Decoding subroutines

Valery Yazkov
<DUBNA>

Table of Contents

DecodeCherenkov
December 1998

Table of Contents




Subroutine DecodeCherenkov decodes data block of Cherenkov detector and called by routine DecodeAll. It has one input parameter ioBlock which pointed what block should be decoded and one output parameter IsOK.

      subroutine DecodeCherenkov(ioBlock,IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InCher and DecTblCher. The most principal are RawData (contains the data read and information about FERA blocks), InCher (common-block /InDataCher/ which accumulate decoded data) and DecTblCher (common-block /DecTblCher/ contains the tables which describe correspondence of ADC-channels to the phototubes of Cherenkov detector).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



After checking the appropriate block number the pointer is set to a data block header and a number of following data word is extracted:

       if(ioBlock.eq.ioBlockCere1) then
        Ptr=PtrBlocksInput(ioBlockCere1,1)
        NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

        nWrd=0
        do while (nWrd.lt.NbWords)
         nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

         if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) are extracted. The pointer to the tables for decoding (iFERA) is found with VSN. A value of iFERA defines type of FERA block (iType).

         VSN=iand(Word,'ff'x)
         iFERA=FromVSN(VSN)
         iType=BlockType(iFERA)

If iType is 1 (register block) then the number of following words is calculated

         if(iType.eq.1) then
          NbWdat=0
C
          Word=ishft(Word,-7)
          do n1=1,7
           Word=ishft(Word,-1)
           if(iand(Word,1).ne.0) NbWdat=NbWdat+1
          end do  !  do n1=1,7

The data word number is checked that the data are not exceeded the block size.

          if((nWrd+NbWdat).gt.NbWords) goto 902

The register data words are skipped because these data taking into account by DAQ in another way.

          nWrd=nWrd+NbWdat
          NbUsed=NbUsed+NbWdat

If iType is 2 (ADC block) then the number number of data words for this module (NbWdat) are extracted

         else if(iType.eq.2) then
          NbWdat=iand(ishft(Word,-11),'f'x)
          if(NbWdat.eq.0) NbWdat=16

iFERA is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

          if(iFERA.le.0) goto 901
          if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

          do n1=1,NbWdat

For each data words a channel number (Chnl) and a amplitude measured are read. The sequential number of arm (iArm) is found. If this number has allowed value the number of amplitudes in Cherenkov detector (NbHitCher) is incremented and an arm number, a phototubes number and amplitude store to arrays of common-block /InDataCher/.

           NbHitCher=NbHitCher+1
           MoHitArmCher(NbHitCher)=iArm
           MoPhTubeCher(NbHitCher)=iPhTbCher(Chnl,iFERA)
           AmplHitCher(NbHitCher)=iand(Word,'7ff'x)

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

          end do  !  do n1=1,NbWdat
          nWrd=nWrd+NbWdat
          NbUsed=NbUsed+NbWdat
         end if  !  if(iType.eq.1) then
        end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

        if(NbUsed.lt.NbWords) goto 904
       end if  !  if(ioBlock.eq.ioBlockCere1) then
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraCher)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraCher

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundCher(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundCher(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundCher defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundCher(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraCher
        notReadyDecode=notReadyDecode.or.MyBlcFoundCher(n1).eq.0
       end do  !  do n1=1,NbFeraCher
C
       goto 1

DecodeDC
December 1998

Table of Contents




Subroutine DecodeDC decodes data block of drift chambers (DC) and called by routine DecodeAll. Subroutine has one input parameter ioBlock which pointed what block should be decoded and one output parameter IsOK.

      subroutine DecodeDC(ioBlock,IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected numbers of plate and driver in DC0
                 2 wire number is out of range in DC0
                 3 unexpected' numbers of plate and driver in DC1
                 4 wire number is out of range in DC1
                 5 unexpected numbers of plate and driver in DC2
                 6 wire number is out of range in DC2

The next KEEPs are included into routine: Declare, Blocks, Divers, EventStatus, RawData, GeomDC, UnitsIO, ParamDC, Geom1DC, InDC and DecTblDC. The most principal are RawData (contains the data read), InDC (common-block /InDataDC/ which accumulate decoded data) and DecTblDC (common-block /DecTblDC/ contains the tables for
decoding).



Description of processing


This routine decodes data from 3 data blocks (DC0, DC1 and DC2). Here decoding of DC0 is described. Other is very simular.



Decoding


After checking the appropriate block number the pointer is set to a data block header and a number of following data word is extracted.

       if(ioBlock.eq.ioBlockDC0) then
          Ptr=PtrBlocksInput(ioBlockDC0,1)
          NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

          do nWrd=1,NbWords

For each data words a channel number (iWr), a plate number (iPlt), a driver number (iDrv) and a time (iTmDr) are extracted.

           Word=BufferInput(Ptr+nWrd)
           iDrv=iand(ishft(Word,-19),'7'x)
           iPlt=iand(ishft(Word,-16),'7'x)
           iWr=iand(ishft(Word,-12),'f'x)
           iTmDr=iand(Word,'fff'x)

These values allow us to define a arm number (iArm), a plane number (nPl) and kind of plane (ixy).

           iArm=iArmDC0(iPlt,iDrv)
           ixy=ixyDC0(iPlt,iDrv)
           nPl=nPlDC0(iPlt,iDrv)

The arm number is checked for allowed value

           if(iArm.lt.0) then
            IsOK=1
            return
           end if  !  if(iArm.lt.0) then

The pointer (ioPlane) to the plane description in common-block /GeomDC/ is found and the number of hit wire is calculated taking into account that wire of Y-planes (ixy=2) connected another way.

           ioPlane=ioPlDC(nPl,ixy,iArm)
           if(ixy.ne.2) then
            nWr=1+iWr+(iPlt-MnPltDC0(iPlt,iDrv))*16
           else
            nWr=-3+iWr+(iPlt-MnPltDC0(iPlt,iDrv))*16
           end if  !  if(ixy.eq.1) then

If data come from X- or Y-plane (ixy[IMAGE ]2) then number of stored hits for this plane is compared with maximal allowed one. In addition the wire number is checked in order to exclude the first and the last wire of each plane because this wires have less efficiency and probably another time properties.

           if(ixy.le.2) then
            nHit=NbHitPlxyDC(nPl,ixy,iArm)+1
            if(nHit.le.MxHitPlDC.and.nWr.gt.1.and.
     *         nWr.lt.MbWiresDC(ioPlane)) then

If these conditions are satisfied the number of hit wires in the plane (NbHitPlxyDC) is incremented and the wire number and drift time and store to arrays of common-block /InDataDC/.

             NbHitPlxyDC(nPl,ixy,iArm)=nHit
             LsHitPlxyDC(nHit,nPl,ixy,iArm)=nWr
             iTmHitPlxyDC(nHit,nPl,ixy,iArm)=iTmDr
             TmHitPlxyDC(nHit,nPl,ixy,iArm)=(iTmDr+0.5)
             DrvHitDC(nHit,nPl,ixy,iArm)=iDrv
             PltHitDC(nHit,nPl,ixy,iArm)=iPlt
             BlockHitDC(nHit,nPl,ixy,iArm)=0

For data come from W-plane (ixy=3) an analogous procedure is fulfilled:

           else
            nHit=NbHitPlwDC(nPl,iArm)+1
            if(nHit.le.MxHitPlDC.and.nWr.gt.1.and.
     *         nWr.lt.MbWiresDC(ioPlane)) then
             NbHitPlwDC(nPl,iArm)=nHit
             LsHitPlwDC(nHit,nPl,iArm)=nWr
             iTmHitPlwDC(nHit,nPl,iArm)=iTmDr
             TmHitPlwDC(nHit,nPl,iArm)=(iTmDr+0.5)
             DrvHitDC(nHit,nPl,3,iArm)=iDrv
             PltHitDC(nHit,nPl,3,iArm)=iPlt
             BlockHitDC(nHit,nPl,3,iArm)=0

End of block data words loop. End of DC0 block decoding.

          end do  !  do nWrd=1,NbWords
       endif  !  if(ioBlock.eq.ioBlockDC0) then

These codes are following by codes for decoding DC1 and DC2 data blocks. Absence of data from W-planes is only difference of decoding these blocks.

DecodeDeDx
December 1998

Table of Contents




Subroutine DecodeDeDx decodes data block of DeDx detector and called by routine DecodeAll. It has one output parameter IsOK.

      subroutine DecodeDeDx(IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InDeDx and DecTblDeDx. The most principal are RawData (contains the data read and information about FERA blocks), InDeDx (common-block /InDataDeDx/ which accumulate decoded data) and DecTblDeDx (common-block /DecTblDeDx/ contains the tables which describe correspondence of ADC-channels to the slabs of DeDx detector).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



The pointer is set to a data block header and a number of following data word is extracted:

       Ptr=PtrBlocksInput(ioBlockDeDx,1)
       NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

       nWrd=0
       do while (nWrd.lt.NbWords)
        nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

        if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) are extracted. The pointer to the tables for decoding (iFERA) is found with VSN. A value of iFERA defines type of FERA block (iType).

        VSN=iand(Word,'ff'x)
        iFERA=FromVSN(VSN)
        iType=BlockType(iFERA)

If iType is 1 (register block) then the number of following words is calculated

        if(iType.eq.1) then
         NbWdat=0
C
         Word=ishft(Word,-7)
         do n1=1,7
          Word=ishft(Word,-1)
          if(iand(Word,1).ne.0) NbWdat=NbWdat+1
         end do  !  do n1=1,7

The data word number is checked that the data are not exceeded the block size.

         if((nWrd+NbWdat).gt.NbWords) goto 902

The register data words are skipped because these data taking into account by DAQ in another way.

         nWrd=nWrd+NbWdat
         NbUsed=NbUsed+NbWdat

If iType is 2 (ADC block) then the number number of data words for this module (NbWdat) are extracted

        else if(iType.eq.2) then
         NbWdat=iand(ishft(Word,-11),'f'x)
         if(NbWdat.eq.0) NbWdat=16

iFERA is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

         if(iFERA.le.0) goto 901
         if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

         do n1=1,NbWdat

For each data words a channel number (Chnl) and a amplitude measured are read. The sequential number of plane (Plane) is found. If this number has allowed value the number of hits in DeDx detector (NbHitDeDx) is incremented and an plane number, a slab number and amplitude store to arrays of common-block /InDataDeDx/.

          NbHitDeDx=NbHitDeDx+1
          MoHitPlaneDeDx(NbHitDeDx)=Plane
          MoHitSlabDeDx(NbHitDeDx)=iSlabDeDx(Chnl,iFERA)
          AmplHitDeDx(NbHitDeDx)=iand(Word,'7ff'x)

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

         end do  !  do n1=1,NbWdat
         nWrd=nWrd+NbWdat
         NbUsed=NbUsed+NbWdat
        end if  !  if(iType.eq.1) then
       end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

       if(NbUsed.lt.NbWords) goto 904
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraDeDx)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraDeDx

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundDeDx(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundDeDx(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundDeDx defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundDeDx(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraDeDx
        notReadyDecode=notReadyDecode.or.MyBlcFoundDeDx(n1).eq.0
       end do  !  do n1=1,NbFeraDeDx
C
       goto 1

DecodeHodHor
December 1998

Table of Contents




Subroutine DecodeHodHor decodes data block of Horizontal hodoscope and called by routine DecodeAll. It has one output parameter IsOK.

      subroutine DecodeHodHor(IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InHodH, ParamDC, HodDC and DecTblHHod. The most principal are RawData (contains the data read and information about FERA blocks), InHodH (common-block /InDataHodH/ which accumulate decoded data) and DecTblHHod (common-block
/DecTblHodH/ contains the tables which describe correspondence of ADC-channels to the slabs of Horizontal hodoscope).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



The pointer is set to a data block header and a number of following data word is extracted:

       Ptr=PtrBlocksInput(ioBlockHodHor,1)
       NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

       nWrd=0
       do while (nWrd.lt.NbWords)
        nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

        if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) and number of data words for this module (NbWdat) are extracted. The pointer to the tables for decoding (iADC) is found with VSN.

        VSN=iand(Word,'ff'x)
        iADC=FromVSN(VSN)
        NbWdat=iand(ishft(Word,-11),'f'x)
        if(NbWdat.eq.0) NbWdat=16

iADC is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

        if(iADC.le.0) goto 901
        if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

        do n1=1,NbWdat

For each data words a channel number (Chnl) and a time measured are read. The sequential number of arm (iArm) is found. If this number has not allowed value or if the time value equals 2047 (ADC overflow) then this data word is skipped. If no then the number of hits in Horizontal hodoscope (NbHitHodH) is incremented and an arm number, a slab number and time store to arrays of common-block /InDataHodH/.

         NbHitHodH=NbHitHodH+1
         MoHitArmHodH(NbHitHodH)=iArm
         MoHitSlabHodH(NbHitHodH)=iSlabHodH(Chnl,iADC)
         iTimeHitHodH(NbHitHodH)=iand(Word,'7ff'x)
         TimeHitHodH(NbHitHodH)=(iTimeHitHodH(NbHitHodH)+0.5)

In parallel these data stored to the arrays of common-blocks /HodDC/ which has structure dedicated for using in DC tracking.

         if(NbHitHodDC(2,iArm).lt.MxHitHod) then
          NbHitHodDC(2,iArm)=NbHitHodDC(2,iArm)+1
          LsHitHodDC(NbHitHodDC(2,iArm),2,iArm)=iSlabHodH(Chnl,iADC)
          iTmHitHodDC(NbHitHodDC(2,iArm),2,iArm)=
     *               iTimeHitHodH(NbHitHodH)
          TmHitHodDC(NbHitHodDC(2,iArm),2,iArm)=
     *              TimeHitHodH(NbHitHodH)
         end if  !  if(NbHitHodDC(2,iArm).lt.MxHitHod) then

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

        end do  !  do n1=1,NbWdat
        nWrd=nWrd+NbWdat
        NbUsed=NbUsed+NbWdat
       end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

       if(NbUsed.lt.NbWords) goto 904
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraHodH)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraHodH

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundHodH(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundHodH(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundHodH defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundHodH(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraHodH
        notReadyDecode=notReadyDecode.or.MyBlcFoundHodH(n1).eq.0
       end do  !  do n1=1,NbFeraHodH
C
       goto 1

DecodeHodVer
December 1998

Table of Contents




Subroutine DecodeHodVer decodes data block of Vertical Hodoscope and called by routine DecodeAll. It has one output parameter IsOK.

      subroutine DecodeHodVer(IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InHodV, ParamDC, HodDC and DecTblVHod. The most principal are RawData (contains the data read and information about FERA blocks), InHodV (common-block /InDataHodV/ which accumulate decoded data) and DecTblVHod (common-block
/DecTblHodV/ contains the tables which describe correspondence of ADC-channels to the slabs of Vertical hodoscope).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



The pointer is set to a data block header and a number of following data word is extracted:

       Ptr=PtrBlocksInput(ioBlockHodVer,1)
       NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

       nWrd=0
       do while (nWrd.lt.NbWords)
        nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

        if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) and number of data words for this module (NbWdat) are extracted. The pointer to the tables for decoding (iADC) is found with VSN.

        VSN=iand(Word,'ff'x)
        iADC=FromVSN(VSN)
        NbWdat=iand(ishft(Word,-11),'f'x)
        if(NbWdat.eq.0) NbWdat=16

iADC is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

        if(iADC.le.0) goto 901
        if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

        do n1=1,NbWdat

For each data words a channel number (Chnl) and a time measured are read. The sequential number of arm (iArm) is found. If this number has not allowed value or if the time value equals 2047 (ADC overflow) then this data word is skipped. If no then the number of hits in Vertical hodoscope (NbHitHodV) is incremented and an arm number, a slab number and time store to arrays of common-block /InDataHodV/.

         NbHitHodV=NbHitHodV+1
         MoHitArmHodV(NbHitHodV)=iArm
         MoHitSlabHodV(NbHitHodV)=iSlabHodV(Chnl,iADC)
         iTimeHitHodV(NbHitHodV)=iand(Word,'7ff'x)
         TimeHitHodV(NbHitHodV)=(iTimeHitHodV(NbHitHodV)+0.5)

In parallel these data stored to the arrays of common-blocks /HodDC/ which has structure dedicated for using in DC tracking.

         if(NbHitHodDC(1,iArm).lt.MxHitHod) then
          NbHitHodDC(1,iArm)=NbHitHodDC(1,iArm)+1
          LsHitHodDC(NbHitHodDC(1,iArm),1,iArm)=iSlabHodV(Chnl,iADC)
          iTmHitHodDC(NbHitHodDC(1,iArm),1,iArm)=
     *               iTimeHitHodV(NbHitHodV)
          TmHitHodDC(NbHitHodDC(1,iArm),1,iArm)=
     *              TimeHitHodV(NbHitHodV)
         end if  !  if(NbHitHodDC(1,iArm).lt.MxHitHod) then

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

        end do  !  do n1=1,NbWdat
        nWrd=nWrd+NbWdat
        NbUsed=NbUsed+NbWdat
       end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

       if(NbUsed.lt.NbWords) goto 904
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraHodV)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraHodV

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundHodV(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundHodV(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundHodV defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundHodV(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraHodV
        notReadyDecode=notReadyDecode.or.MyBlcFoundHodV(n1).eq.0
       end do  !  do n1=1,NbFeraHodV
C
       goto 1

DecodeMSGC
December 1998

Table of Contents




Subroutine DecodeMSGC decodes data block of MSGC detector and called by routine DecodeAll. Present version assumes only one plane (and one data block) of MSGC. In future processing of data from some planes will be provided. Subroutine has one input parameter ioBlock which pointed what block should be decoded and one output parameter IsOK.

      subroutine DecodeMSGC(ioBlock,IsOK)

Possible values of IsOK are:

                 0 normal
                 1 Number of data words exceeds the expected number 
                   of words for block

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InMSGC and DecTblMSGC. The most principal are RawData (contains the data read), InMSGC (common-block /InDataMSGC/ which accumulate decoded data) and DecTblMSGC (common-block /DecTblMSGC/ contains the tables of pedestals).



Description of processing
1. Decoding


After checking the appropriate block number the pointer is set to a data block header and a number of following data word is extracted. The plane number is assumed to be 1.

       if(ioBlock.eq.ioBlockMSGCm0) then
        Ptr=PtrBlocksInput(ioBlockMSGCm0,1)
        NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)
        Plane=1

The number of data word is checked that the data are not exceeded expected one.

        if(NbWords.gt.MaxNbHitMSGC) goto 901

Block data words loop begins:

        do nWrd=1,NbWords

For each data words a channel number (Chnl) and a amplitude measured are read and store to arrays of common-block /InDataMSGC/ together with plane number.

         Word=BufferInput(Ptr+nWrd)
         Chnl=iand(ishft(Word,-8),'1ff'x)+1
         MoHitPlaneMSGC(Chnl)=Plane
         MoHitSlabMSGC(Chnl)=Chnl
         AmplHitMSGC(Chnl)=iand(Word,'ff'x)

End of block data words loop.



2. Zero suppression



The number of read (NbWords) words compared with the number of channels for MSGC plane (MaxNbHitMSGC). If NbWords<MaxNbHitMSGC (pedestal suppression mode) then procedure of zero suppression starts.

        if(NbWords.lt.MaxNbHitMSGC) then
         do Chnl=1,MaxNbHitMSGC
          if(MoHitPlaneMSGC(Chnl).le.0) cycle
          NbHitMSGC=NbHitMSGC+1
          MoHitPlaneMSGC(NbHitMSGC)=MoHitPlaneMSGC(Chnl)
          MoHitSlabMSGC(NbHitMSGC)=MoHitSlabMSGC(Chnl)
          AmplHitMSGC(NbHitMSGC)=AmplHitMSGC(Chnl)
         end do  !  do Chnl=1,MaxNbHitMSGC

After this procedure the number of hit strips (NbHitMSGC) is calculated and data recorded to lowest NbHitMSGC cells of arrays.

If NbWords=MaxNbHitMSGC (without pedestal suppression) NbHitMSGC is assigned by NbWords.

        else
         NbHitMSGC=NbWords
        end if  !  if(NbWords.lt.MaxNbHitMSGC) then

The finish of decoding.

       end if  !  if(ioBlock.eq.ioBlockMSGCm0) then
      return
<

DecodeMuon
December 1998

Table of Contents




Subroutine DecodeMuon decodes data block of Muon detector and called by routine DecodeAll. It has one output parameter IsOK.

      subroutine DecodeMuon(IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InMuon and DecTblMuon. The most principal are RawData (contains the data read and information about FERA blocks), InMuon (common-block /InDataMuon/ which accumulate decoded data) and DecTblMuon (common-block /DecTblMuon/ contains the tables which describe correspondence of ADC-channels to the slabs of Muon detector).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



The pointer is set to a data block header and a number of following data word is extracted:

       Ptr=PtrBlocksInput(ioBlockMuon,1)
       NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

       nWrd=0
       do while (nWrd.lt.NbWords)
        nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

        if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) and number of data words for this module (NbWdat) are extracted. The pointer to the tables for decoding (iADC) is found with VSN.

        VSN=iand(Word,'ff'x)
        iADC=FromVSN(VSN)
        NbWdat=iand(ishft(Word,-11),'f'x)
        if(NbWdat.eq.0) NbWdat=16

iADC is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

        if(iADC.le.0) goto 901
        if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

        do n1=1,NbWdat

For each data words a channel number (Chnl) and a amplitude measured are read. The sequential number of arm (iArm) is found. If this number has allowed value the number of hits in Muon detector (NbHitMuon) is incremented and an arm number, a slab number and amplitude store to arrays of common-block /InDataMuon/.

         NbHitMuon=NbHitMuon+1
         MoHitArmMuon(NbHitMuon)=iArm
         MoHitSlabMuon(NbHitMuon)=iSlabMuon(Chnl,iADC)
         AmplHitMuon(NbHitMuon)=iand(Word,'7ff'x)

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

        end do  !  do n1=1,NbWdat
        nWrd=nWrd+NbWdat
        NbUsed=NbUsed+NbWdat
       end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

       if(NbUsed.lt.NbWords) goto 904
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraMuon)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraMuon

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundMuon(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundMuon(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundMuon defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundMuon(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraMuon
        notReadyDecode=notReadyDecode.or.MyBlcFoundMuon(n1).eq.0
       end do  !  do n1=1,NbFeraMuon
C
       goto 1

DecodePreShower
December 1998

Table of Contents




Subroutine DecodePreShower decodes data block of PreShower detector and called by routine DecodeAll. It has one output parameter IsOK.

      subroutine DecodePreShower(IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InPrSh and DecTblPrSh. The most principal are RawData (contains the data read and information about FERA blocks), InPrSh (common-block /InDataPrSh/ which accumulate decoded data) and DecTblPrSh (common-block /DecTblPrSh/ contains the tables which describe correspondence of ADC-channels to the slabs of PreShower detector).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



The pointer is set to a data block header and a number of following data word is extracted:

       Ptr=PtrBlocksInput(ioBlockPreShower,1)
       NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

       nWrd=0
       do while (nWrd.lt.NbWords)
        nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

        if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) and number of data words for this module (NbWdat) are extracted. The pointer to the tables for decoding (iADC) is found with VSN.

        VSN=iand(Word,'ff'x)
        iADC=FromVSN(VSN)
        NbWdat=iand(ishft(Word,-11),'f'x)
        if(NbWdat.eq.0) NbWdat=16

iADC is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

        if(iADC.le.0) goto 901
        if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

        do n1=1,NbWdat

For each data words a channel number (Chnl) and a amplitude measured are read. The sequential number of arm (iArm) is found. If this number has allowed value the number of hits in PreShower detector (NbHitPrSh) is incremented and an arm number, a slab number and amplitude store to arrays of common-block /InDataPrSh/.

         NbHitPrSh=NbHitPrSh+1
         MoHitArmPrSh(NbHitPrSh)=iArm
         MoHitSlabPrSh(NbHitPrSh)=iSlabPrSh(Chnl,iADC)
         AmplHitPrSh(NbHitPrSh)=iand(Word,'7ff'x)

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

        end do  !  do n1=1,NbWdat
        nWrd=nWrd+NbWdat
        NbUsed=NbUsed+NbWdat
       end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

       if(NbUsed.lt.NbWords) goto 904
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraPrSh)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraPrSh

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundPrSh(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundPrSh(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundPrSh defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundPrSh(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraPrSh
        notReadyDecode=notReadyDecode.or.MyBlcFoundPrSh(n1).eq.0
       end do  !  do n1=1,NbFeraPrSh
C
       goto 1

DecodeScFi
December 1998

Table of Contents




Subroutine DecodeScFi decodes data block of ScFi detector and called by routine DecodeAll. It has one output parameter IsOK.

      subroutine DecodeScFi(IsOK)

Possible values of IsOK are:

                 0 normal
                 1 unexpected VSN numbers
                 2 Number of data words exceeds the number of words
                   for block
                 3 unexpected channel
                 4 there are unused words
                 5 Needed FERA block descriptions were not found

The next KEEPs are included into routine: Declare, Blocks, Divers, UnitsIO, EventStatus, RawData, InScFi and DecTblScFi. The most principal are RawData (contains the data read and information about FERA blocks), InScFi (common-block /InDataScFi/ which accumulate decoded data) and DecTblScFi (common-block /DecTblScFi/ contains the tables which describe correspondence of TDC-channels to the slabs of ScFi detector and ADC-channels to the ScFi phototube).



Description of processing


At the beginning current run number is compared with local one. If they are different the procedure of the routine initialisation performs (see below).

       IsOK=0
       if(NoRun.ne.NoRunLc) goto 800



If initialisation is successful then decoding starts.



1. Decoding



The pointer is set to a data block header and a number of following data word is extracted:

       Ptr=PtrBlocksInput(ioBlockScFi,1)
       NbWords=iand(ishft(BufferInput(Ptr),-16),'ffff'x)

Block data words loop begins:

       nWrd=0
       do while (nWrd.lt.NbWords)
        nWrd=nWrd+1

A word content is tested: is this word a header word for FERA module?

        if(iand(Word,'8000'x).eq.0) then

If it is true then the VSN of module (VSN) are extracted. The pointer to the tables for decoding (iFERA) is found with VSN. A value of iFERA defines type of FERA block (iType).

        VSN=iand(Word,'ff'x)
        iFERA=FromVSN(VSN)
        iType=BlockType(iFERA)

If iType is 1 (register block) then the number of following words is calculated

        if(iType.eq.1) then
         NbWdat=0
C
         Word=ishft(Word,-7)
         do n1=1,7
          Word=ishft(Word,-1)
          if(iand(Word,1).ne.0) NbWdat=NbWdat+1
         end do  !  do n1=1,7

The data word number is checked that the data are not exceeded the block size.

         if((nWrd+NbWdat).gt.NbWords) goto 902

The register data words are skipped because these data taking into account by DAQ in another way.

         nWrd=nWrd+NbWdat
         NbUsed=NbUsed+NbWdat

If iType is 2 (TDC block) then the data shift number and flag for leading edge are extracted.

         DataShift=iand(ishft(Word,-8),'3'x)
         LdngEdge=iand(ishft(Word,-10),'1'x)

iFERA is checked for allowed value.

         if(iFERA.le.0) goto 901

FERA module data word loop begins. It is terminated by next header word or by end of block.

         NbWdat=0
         do n1=1,min(32,NbWords-nWrd)
          Word=BufferInput((Ptr+nWrd)+n1)
          if(iand(Word,'8000'x).ne.0) exit

For each data words a channel number (Chnl) and a time measured are read. The sequential number of plane (Plane) is found. If this number has allowed value the number of hits in ScFi detector (NbHitScFi) is incremented and an plane number, a slab number and amplitude store to arrays of common-block /InDataScFi/.

          NbHitScFi=NbHitScFi+1
          MoHitPlaneScFi(NbHitScFi)=Plane
          MoHitSlabScFi(NbHitScFi)=iSlabScFi(Chnl,iFERA)
          iTimeHitScFi(NbHitScFi)=ishft(iTime,DataShift)
          TimeHitScFi(NbHitScFi)=(iTimeHitScFi(NbHitScFi)+0.5)

End of FERA module data words loop. Number of block data words and number of used words are incremented by the number of FERA module data words. End of block data words loop.

         end do  !  do n1=1,NbWdat
         nWrd=nWrd+NbWdat
         NbUsed=NbUsed+NbWdat

If iType is 3 (ADC block) then the number number of data words for this module (NbWdat) are extracted

        else if(iType.eq.3) then
         NbWdat=iand(ishft(Word,-11),'f'x)
         if(NbWdat.eq.0) NbWdat=16

iFERA is checked for allowed value and NbWdat is checked that the data are not exceeded the block size.

         if(iFERA.le.0) goto 901
         if((nWrd+NbWdat).gt.NbWords) goto 902

FERA module data word loop begins:

         do n1=1,NbWdat

For each data words a channel number (Chnl) and a amplitude measured are read. The sequential number of plane (Plane) is found. If this number has allowed value the number of hits in ScFi detector (NbMsVoltScFi) is incremented and an plane number, a phototube number and amplitude store to arrays of common-block /InDataScFi/.

          NbMsVoltScFi=NbMsVoltScFi+1
          MoMsPlaneScFi(NbMsVoltScFi)=Plane
          MoMsPhTbScFi(NbMsVoltScFi)=iSlabScFi(Chnl,iFERA)
          VoltPhTbScFi(NbMsVoltScFi)=iand(Word,'7ff'x)

End of FERA module data words loop. Number of block data words and Number of used words are incremented by the number of FERA module data words. End of block data words loop.

         end do  !  do n1=1,NbWdat
         nWrd=nWrd+NbWdat
         NbUsed=NbUsed+NbWdat
        end if  !  if(iType.eq.1) then
       end do  !  do nWrd=1,NbWords

The presence of unrecognized words is checked but now the IsOK value remain 0 (normal) even if such words are found because changes of electronics configuration occur very often during run in November-December of 1998. In future this check will be ON. The finish of decoding.

       if(NbUsed.lt.NbWords) goto 904
       return



2. Initialisation



The current run number is assigned to local run number. The local arrays used in initialization are filled by zero.

 800   NoRunLc=NoRun
       call vzero(FromVSN(0),MaxFeras+1)
       call vzero(VSNfound,NbFeraScFi)

Begin of loop over described FERA modules.

       do n1=0,MaxFeras

Begin of loop over expected FERA modules.

        do n2=1,NbFeraScFi

The names (FeraNames) and types (FeraTypes) read from run-blocks are compared with expected MyName and MyType. If MyBlcFoundScFi(n2) less than zero this block is suitable for this routine but not expected in the current run.

         bf=0
         if(MyBlcFoundScFi(n2).ge.0.and.ChTmp.eq.MyName(n2)) then
          ChTmp=' '
          ChTmp=FeraTypes(n1)
          if(ChTmp.eq.MyType(n2)) then
           bf=n2
          else
           bf=-1
          end if  !  if(ChTmp.eq.MyType(n2)) then
         end if  !  if(ChTmp.eq.MyName(n2)) then

If they coincide then cell of array FromVSN which corresponds to VSN of FeraNames get the sequential number of expected block. VSNfound array contain the inverse reference. MyBlcFoundScFi defined by 1. It means that block is found.

         if(bf.gt.0) then
          FromVSN(n1)=bf
          MyBlcFoundScFi(bf)=1
          VSNfound(bf)=n1
         end if  !  if(bf.gt.0) then

End of loops over existed and expected FERA modules

        end do  !  do n2=1,2
       end do  !  do n1=0,MaxFeras

Check the presence all needed blocks and go to decoding step.

       notReadyDecode=.false.
       do n1=1,NbFeraScFi
        notReadyDecode=notReadyDecode.or.MyBlcFoundScFi(n1).eq.0
       end do  !  do n1=1,NbFeraScFi
C
       goto 1