AIDA GELINA BRIKEN nToF CRIB ISOLDE CIRCE nTOFCapture DESPEC DTAS EDI_PSA 179Ta CARME StellarModelling DCF K40
  DESPEC  ELOG logo
Message ID: 10     Entry time: Sat Dec 1 16:43:47 2018
Author: TD 
Subject: Analysis of WRTest28Nov18.dat 
Attachment 1 - analyser.f 

Modified version of TDR format analyser program to handle 64 bit WR timestamps

Attachment 2 - analyser program output

12092 blocks = 773888kb

8 timewarps

0 information code 5 data items

data file does not commence with either information codes 5 or 4

times/rates not correctly calculated - program assumes 10ns/tick 

Attachment 3 - od -x output 
Attachment 1: analyser.f  21 kB  | Hide | Hide all
      PROGRAM GREAT

C     Read and analyse GREAT format data - version 3.3.0
C
C     See:
C     http://npg.dl.ac.uk/documents/edoc504/edoc504.html
C     http://npg.dl.ac.uk/DataAcq/TSformat.html

      IMPLICIT NONE                                 
C
C     External functions
C
      EXTERNAL timestamp
C
      DOUBLE PRECISION dfloat
C
      INTEGER and
      INTEGER*8 iargc
      INTEGER rshift
      INTEGER*8 timestamp
C
      REAL secnds
C
C     Parameter variables
C
      INTEGER block_length
      PARAMETER (block_length = 16384)
C
C     Local variables
C
      CHARACTER*255 arg
      CHARACTER*(block_length*4) buffer
      CHARACTER*255 filename
C
      INTEGER adc_data, block_number, block_ptr, ch, channel
      INTEGER channel_ident, data_block(block_length)
      INTEGER*8 dead(32)
      INTEGER event, fail
      INTEGER*8 first_ts
      INTEGER i
      INTEGER*2 i2(2), i2_2(4)
      INTEGER i4, i4_2(2)
      INTEGER*8 i8, idle(32)
      INTEGER information, information_index, io_error, items(0:32,0:31)
      INTEGER j, j4
      INTEGER*8 last_ts
      INTEGER mbs_data, module
      INTEGER*8 pause(32)
      INTEGER range
      INTEGER*8 resume(32)
      INTEGER sample_length, sum(0:31)
      INTEGER*8 sync(32)
      INTEGER tag, tag_old
      INTEGER*8 ts
      INTEGER ts28, ts48, ts64
      INTEGER*8 ts_old
      INTEGER type, type_old
C
      LOGICAL verbose
C
      REAL dt, t1, t2

      EQUIVALENCE ( data_block, buffer )
      EQUIVALENCE ( i4, i2( 1 ) )
      EQUIVALENCE ( i8, i4_2(1) )

      SAVE data_block, block_ptr, block_number, event

C----67---------------------------------------------------------------72------80
C     Announce program

      WRITE( 6, 9000 )

C     Initialise variables

      block_ptr = 1
      block_number = 0
      event = 0

      i4 = 0
      i8 = 0

      ts_old = 0
      tag_old = 0
      type_old = 0
      first_ts = 0
      last_ts = 0
      ts28 = 0
      ts48 = 0
      ts64 = 0

      type = 0
      
      verbose = .FALSE.
      
      DO i = 0, 32
       DO j = 0, 31
        sum( j ) = 0
        items( i, j ) = 0
       ENDDO
      ENDDO

      DO i = 1, 32
       pause( i ) = -1
       resume( i ) = -1
       dead( i ) = 0
       sync( i ) = 0
       idle( i ) = 0
      ENDDO

C     Get input filename from command line argument

      DO i = 1, iargc()
       CALL getarg( i, arg )
       IF ( arg.EQ.'v') THEN
        verbose = .TRUE.
        write(6,*) ' verbose'
       ELSE
        filename = arg
       ENDIF
      ENDDO
      IF ( iargc().LT.1 .OR. iargc().GT.2 ) THEN
       WRITE( 6, * ) ' Usage: ./a.exe [v] <filename>'
       STOP
      ENDIF

      t1 = SECNDS( 0.0 )

C     Open file

      OPEN( 10, RECL = 4 * block_length,
     +      FILE = filename, STATUS = 'OLD', ACCESS = 'DIRECT' )

    1 CONTINUE

C     Read next block
C     Note: for FORTRAN direct I/O first block/record number is 1
C           for GREAT data format first (encoded) block/record number is 0

      block_number = block_number + 1

      READ( 10, REC = block_number, iostat=io_error, ERR=1000 ) buffer

      DO block_ptr = 7, data_block( 6 ) / 4 + 4, 2


       i4 = data_block( block_ptr )
       j4 = data_block( block_ptr + 1 )

       tag = AND( RSHIFT( i4, 30 ), Z'00000003' )

       module = 0
       type = 0

C      tag = 3 = ADC data format
C      tag = 2 = Other data
C      tag = 1 = Sample trace buffer format
C      tag = 0 = undefined?

C----67---------------------------------------------------------------72------80
C     ADC data

       IF ( tag.EQ.3 ) THEN

        fail = AND( RSHIFT( i4, 29 ), Z'00000001' )

        IF ( fail.NE.0 ) THEN

         WRITE( 6, 9600 ) block_number, block_ptr, i4

        ENDIF

        range = AND( RSHIFT( i4, 28 ), Z'00000001' )
        channel_ident = AND( RSHIFT( i4, 16 ), Z'00000fff' )
        module = AND( RSHIFT( channel_ident, 6 ), Z'0000003f' )
        IF ( range.EQ.1 ) THEN
         items(module, 19 ) = items(module, 19 ) + 1
        ENDIF
        channel = AND( channel_ident, Z'0000003f' )
        adc_data = AND( i4, Z'0000ffff' )

        items(module, 0 ) = items(module, 0 ) + 1

        ts28 = AND( data_block( block_ptr + 1 ), Z'0fffffff' )

        ts = timestamp( ts64, ts48, ts28, type )

	IF ( ts.LT.ts_old ) THEN

	 items(module, 20 ) = items(module, 20 ) + 1

         WRITE( 6, 9710 ) block_number, block_ptr, i4, module, fail,
     +   range, channel_ident, channel, adc_data, ts, ts_old, ts_old-ts,
     +   tag_old, type_old
        ENDIF

        ts_old = ts
        tag_old = tag
        type_old = 0

        IF ( verbose ) THEN 
         WRITE( 6, 9700 ) block_number, block_ptr, i4, module, fail,
     +   range, channel_ident, channel, adc_data, ts
        ENDIF

        ch = channel + ( module - 1 ) * 64 + ( range * 2048 )

C----67---------------------------------------------------------------72------80
C     Other information

       ELSEIF( tag.EQ.2 ) THEN

        module = AND( RSHIFT( i4, 24 ), Z'0000003f' )
        type = AND( RSHIFT( i4, 20 ), Z'0000000f' )
        information = AND( i4, Z'000fffff' )

        items(module, 1 ) = items(module, 1 ) + 1

        ts28 = AND( data_block( block_ptr + 1 ), Z'0fffffff' )

        IF ( type.EQ.2 ) THEN

C----67---------------------------------------------------------------72------80
C     PAUSE timestamp

         items(module, 4 ) = items(module, 4 ) + 1

        ts48 = information
C        ts = timestamp( ts48, ts28, type )

         ts = timestamp( ts64, ts48, ts28, type )

         IF ( ts.LT.ts_old ) THEN

          items(module, 21 ) = items(module, 21 ) + 1

         ENDIF
         ts_old = ts
         type_old = type
         tag_old = tag
         pause( module ) = ts

         IF ( verbose ) THEN 
          WRITE( 6, 9800 ) block_number, block_ptr, i4, module, type,
     +     information, ts
         ENDIF

        ELSEIF( type.EQ.3 ) THEN

C----67---------------------------------------------------------------72------80
C     RESUME timestamp

         items(module, 5 ) = items(module, 5 ) + 1

         ts48 = information
C         ts = timestamp( ts48, ts28, type )

         ts = timestamp( ts64, ts48, ts28, type )

         IF ( ts.LT.ts_old ) THEN

          items(module, 22 ) = items(module, 22 ) + 1

         ENDIF
         ts_old = ts
         type_old = type
         tag_old = tag
         resume( module ) = ts

         IF ( resume( module ).GE.0 
     +         .AND.
     +        pause( module ).GE.0 
     +          .AND.
     +        resume( module ).GE.pause( module ) ) THEN
          dead( module ) = ( resume( module ) - pause( module ) ) 
     +                     + dead( module )
          pause( module ) = -1
          resume( module ) = -1
         ENDIF

         IF ( verbose ) THEN 
          WRITE( 6, 9810 ) block_number, block_ptr, i4, module, type,
     +     information, ts
         ENDIF

        ELSEIF( type.EQ.4 ) THEN

C----67---------------------------------------------------------------72------80
C     SYNC100 timestamp/White Rabbit Timestamp Marker (bits 28-47)

         items(module, 6 ) = items(module, 6 ) + 1

         ts48 = information

C        ts = timestamp( ts48, ts28, type )
         ts = timestamp( ts64, ts48, ts28, type )


         IF ( first_ts.EQ.0 ) THEN
          first_ts = ts 
... 446 more lines ...
Attachment 2: WRTest28Nov18.out  12 kB  | Hide | Hide all
 *** TDR format 3.3.0 analyser - TD - May 2018
 ***   SYNC100 timestamp: block:  3972 ptr:   129 data: 0x824AAF3C module:  2 information type:  4 information field: 0x000AAF3C ts: 0x0000AAF3C0000007 OLD: ts: 0x0000AAF43FB60119 dt: 0x000000007FB60112 tag: 3 type: 0
 ***   SYNC100 timestamp: block:  4117 ptr:    17 data: 0x834AB4EE module:  3 information type:  4 information field: 0x000AB4EE ts: 0x0000AB4EEFFFFFFE OLD: ts: 0x0000AB4F6FE2FB16 dt: 0x000000007FE2FB18 tag: 3 type: 0
 *** FEE64 discriminator: block:  6321 ptr:     7 data: 0x82640001 module:  2 information type:  6 information field: 0x00040001 ts: 0x0000B0BA95E8A4BB OLD: ts: 0x0000B0BA9C641977 dt: 0x00000000067B74BC tag: 3 type: 0
 ***   SYNC100 timestamp: block:  6321 ptr:   359 data: 0x824B0BA3 module:  2 information type:  4 information field: 0x000B0BA3 ts: 0x0000B0BA30000007 OLD: ts: 0x0000B0BA9FD5AFB9 dt: 0x000000006FD5AFB2 tag: 3 type: 0
 *** FEE64 discriminator: block:  8168 ptr:     7 data: 0x83610100 module:  3 information type:  6 information field: 0x00010100 ts: 0x0000B545700D8F24 OLD: ts: 0x0000B545737361F0 dt: 0x000000000365D2CC tag: 3 type: 0
 ***   SYNC100 timestamp: block:  8168 ptr:   389 data: 0x834B5451 module:  3 information type:  4 information field: 0x000B5451 ts: 0x0000B54510000006 OLD: ts: 0x0000B5457F907F06 dt: 0x000000006F907F00 tag: 3 type: 0
 ***            ADC data: block:  9068 ptr:     7 data: 0xC0A0746E module:  2 fail: 0 range: 0 id:   160 channel: 32 adc: 29806  ts: 0x0000B77C0CB89539 OLD: ts: 0x0000B77C0FFFFFFF dt: 0x0000000003476AC6 tag: 2 type: 4
 ***   SYNC100 timestamp: block:  9068 ptr:   125 data: 0x824B77BA module:  2 information type:  4 information field: 0x000B77BA ts: 0x0000B77BA0000001 OLD: ts: 0x0000B77C0FD296D9 dt: 0x000000006FD296D8 tag: 3 type: 0
 *** ERROR: READ I/O error:       5002
                   blocks:      12092
          ADC data format:   54772761 (    1675.2 Hz)
        Other data format:   44212351 (    1352.2 Hz)
 Sample trace data format:          0 (       0.0 Hz)
         Undefined format:          0 (       0.0 Hz)
   Other data format type:      PAUSE:          0 (       0.0 Hz)
                               RESUME:          0 (       0.0 Hz)
                              SYNC100:     487184 (      14.9 Hz)
                              WR48-63:          0 (       0.0 Hz)
                           FEE64 disc:   43725167 (    1337.3 Hz)
                             MBS info:          0 (       0.0 Hz)
                           Other info:          0 (       0.0 Hz)

   ADC data range bit set:          0 (       0.0 Hz)

                Timewarps:        ADC:          1 (       0.0 Hz)
                                PAUSE:          0 (       0.0 Hz)
                               RESUME:          0 (       0.0 Hz)
                              SYNC100:          5 (       0.0 Hz)
                              WR48-63:          0 (       0.0 Hz)
                           FEE64 disc:          2 (       0.0 Hz)
                             MBS info:          0 (       0.0 Hz)
                            Undefined:          0 (       0.0 Hz)
                         Sample trace:          0 (       0.0 Hz)

 *** Timestamp elapsed time:    32695.408 s
 FEE  elapsed dead time(s) elapsed idle time(s)
  1                0.000           326951.701
  2                0.000           327002.704
  3                0.000           326986.598
  4                0.000           326951.701
  5                0.000                0.000
  6                0.000                0.000
  7                0.000                0.000
  8                0.000                0.000
  9                0.000                0.000
 10                0.000                0.000
 11                0.000                0.000
 12                0.000                0.000
 13                0.000                0.000
 14                0.000                0.000
 15                0.000                0.000
 16                0.000                0.000
 17                0.000                0.000
 18                0.000                0.000
 19                0.000                0.000
 20                0.000                0.000
 21                0.000                0.000
 22                0.000                0.000
 23                0.000                0.000
 24                0.000                0.000
 25                0.000                0.000
 26                0.000                0.000
 27                0.000                0.000
 28                0.000                0.000
 29                0.000                0.000
 30                0.000                0.000
 31                0.000                0.000
 32                0.000                0.000

 *** Statistics
 FEE  ADC Data Other Data     Sample  Undefined      Pause     Resume    SYNC100    WR48-63       Disc        MBS      Other   HEC Data
  0          0          0          0          0          0          0          0          0          0          0          0          0
  1   14927838   11937352          0          0          0          0     121789          0   11815563          0          0          0
  2   14930026   12391697          0          0          0          0     121806          0   12269891          0          0          0
  3    9966853    9183853          0          0          0          0     121802          0    9062051          0          0          0
  4   14948044   10699449          0          0          0          0     121787          0   10577662          0          0          0
  5          0          0          0          0          0          0          0          0          0          0          0          0
  6          0          0          0          0          0          0          0          0          0          0          0          0
  7          0          0          0          0          0          0          0          0          0          0          0          0
  8          0          0          0          0          0          0          0          0          0          0          0          0
  9          0          0          0          0          0          0          0          0          0          0          0          0
 10          0          0          0          0          0          0          0          0          0          0          0          0
 11          0          0          0          0          0          0          0          0          0          0          0          0
 12          0          0          0          0          0          0          0          0          0          0          0          0
 13          0          0          0          0          0          0          0          0          0          0          0          0
 14          0          0          0          0          0          0          0          0          0          0          0          0
 15          0          0          0          0          0          0          0          0          0          0          0          0
 16          0          0          0          0          0          0          0          0          0          0          0          0
 17          0          0          0          0          0          0          0          0          0          0          0          0
 18          0          0          0          0          0          0          0          0          0          0          0          0
 19          0          0          0          0          0          0          0          0          0          0          0          0
 20          0          0          0          0          0          0          0          0          0          0          0          0
 21          0          0          0          0          0          0          0          0          0          0          0          0
 22          0          0          0          0          0          0          0          0          0          0          0          0
 23          0          0          0          0          0          0          0          0          0          0          0          0
 24          0          0          0          0          0          0          0          0          0          0          0          0
 25          0          0          0          0          0          0          0          0          0          0          0          0
 26          0          0          0          0          0          0          0          0          0          0          0          0
 27          0          0          0          0          0          0          0          0          0          0          0          0
 28          0          0          0          0          0          0          0          0          0          0          0          0
 29          0          0          0          0          0          0          0          0          0          0          0          0
 30          0          0          0          0          0          0          0          0          0          0          0          0
 31          0          0          0          0          0          0          0          0          0          0          0          0
 32          0          0          0          0          0          0          0          0          0          0          0          0

 *** Timewarps
 FEE       ADC      Pause     Resume    SYNC100    WR48-63       Disc        MBS  Undefined    Samples
  0          0          0          0          0          0          0          0          0          0
  1          0          0          0          0          0          0          0          0          0
  2          1          0          0          3          0          1          0          0          0
  3          0          0          0          2          0          1          0          0          0
  4          0          0          0          0          0          0          0          0          0
  5          0          0          0          0          0          0          0          0          0
  6          0          0          0          0          0          0          0          0          0
  7          0          0          0          0          0          0          0          0          0
  8          0          0          0          0          0          0          0          0          0
  9          0          0          0          0          0          0          0          0          0
 10          0          0          0          0          0          0          0          0          0
 11          0          0          0          0          0          0          0          0          0
 12          0          0          0          0          0          0          0          0          0
 13          0          0          0          0          0          0          0          0          0
 14          0          0          0          0          0          0          0          0          0
 15          0          0          0          0          0          0          0          0          0
 16          0          0          0          0          0          0          0          0          0
 17          0          0          0          0          0          0          0          0          0
 18          0          0          0          0          0          0          0          0          0
 19          0          0          0          0          0          0          0          0          0
 20          0          0          0          0          0          0          0          0          0
 21          0          0          0          0          0          0          0          0          0
 22          0          0          0          0          0          0          0          0          0
 23          0          0          0          0          0          0          0          0          0
 24          0          0          0          0          0          0          0          0          0
 25          0          0          0          0          0          0          0          0          0
 26          0          0          0          0          0          0          0          0          0
 27          0          0          0          0          0          0          0          0          0
 28          0          0          0          0          0          0          0          0          0
 29          0          0          0          0          0          0          0          0          0
 30          0          0          0          0          0          0          0          0          0
 31          0          0          0          0          0          0          0          0          0
 32          0          0          0          0          0          0          0          0          0

 *** Program elapsed time:    6.453s ( 1873.821 blocks/s, 117.114 Mb/s)
Attachment 3: Capture.PNG  205 kB  | Hide | Hide all
Capture.PNG
ELOG V3.1.4-unknown