[KLOE] [Offline Doc] [TRK Files]

Track Reconstruction Library

vtxfin.kloe


C       ===============================================
C       VTXFIN - VerTeX FINder module
C       ===============================================
C
C       Language:
C       =========
C       KLOE Fortran
C       
C       Modulename:
C       ===========
C       VTXFIN_MOD.KLOE
C
C       Description:
C       ============
C
C       Author:
C       =======
C	M.Incagli
C
C       Creation Date: 15 Sep 1997
C       ==========================
C
C       Declare ="VTXFIN_DEC",
C	Init    ="VTXFIN_IN",
C	Talk    ="VTXFIN_TK",
C       Run_Init="VTXFIN_RIN",
C       Book    ="VTXFIN_HB",
C       Event   ="VTXFIN_EV",
C       Fini    ="VTXFIN_END"
C===============================================================================
	Subroutine VTXFIN_IN
C===============================================================================
c
c
$$IMPLICIT NONE
$$INCLUDE 'K$ITRK:VTXFIN.INC'
c
C===============================================================================

	RETURN
	END

C===============================================================================
	Subroutine VTXFIN_HB
C===============================================================================
$$IMPLICIT
$$INCLUDE 'K$ITRK:VTXFIN.INC'
C===============================================================================

	RETURN
	END

C===============================================================================
	Subroutine VTXFIN_TK
C===============================================================================
$$IMPLICIT
$$INCLUDE 'K$ITRK:VTXFIN.INC'
C===============================================================================
        INTEGER ISTAT, UIGTYE, UIGTRE
C===============================================================================
c       ISTAT = UIGTYE(' VTXFIN_TK> TDC Offset On?',TZERON)
c
c        ISTAT = UIGTRE(' VTXFIN_TK> DR (CM) for merging :',
c     +          R_THR,0.,100.)
c        ISTAT = UIGTRE(' VTXFIN_TK> DR TRANSVERSE (CM) for merging:',
c     +          RT_THR,0.,100.)
c        ISTAT = UIGTRE(' VTXFIN_TK> Dist on fiber (cm) for merging:',
c     +          Z_THR,0.,100.)
c        ISTAT = UIGTRE(' VTXFIN_TK> Time diff (ns) for merging:',
c     +          T_THR,0.,100.)
c        ISTAT = UIGTRE(' VTXFIN_TK> Ene (MEV) to accept clust:',
c     +          ECMIN,0.,100.)
c        ISTAT = UIGTRE(' VTXFIN_TK> T RMS threshold for preclusters:',
c     +          RMSMAX,0.,10.)
	RETURN
	END

C===============================================================================
        SUBROUTINE VTXFIN_RIN
C===============================================================================
$$IMPLICIT NONE
$$INCLUDE 'K$ITRK:VTXFIN.INC'
c
c
C------ External Declarations --------------------------------------------------
c
c        integer geo_init, geo_cccp, calpoiupk, cal_init
c
c------ Local Declarations-----------------------------------------------------
c
c	real    dummy						
c	
c        INTEGER ISTAT, LUN1, LUN2, IARR(4), CALPOI, I , J
c
c====== Start of executable Code ===============================================
cc
        RETURN
        END
C===============================================================================

	Subroutine VTXFIN_END

$$IMPLICIT NONE

	RETURN
	END

C===============================================================================
	subroutine VTXFIN_EV
c	======================
c
c	Description: 
c	------------ 
c	Reads DTFS banks and looks for vertices
c
c	Input Parameters: none
c	-----------------
c
c	Output Parameters: none
c	------------------
c
c------ Global Declarations ----------------------------------------------------
c
$$implicit none
c
c------ Include Files ----------------------------------------------------------
c
$$Include 'K$inc:Bcs.INC'
$$include 'ybos$library:errcod.inc'
$$include 'k$inc:jobsta.inc'				
$$include 'k$inc:erlevl.inc'                    ! error logger
$$include 'K$ITRK:VTXFIN.inc'
$$include 'K$ITRK:VWRK.inc'
$$include 'K$ITRK:DCHD.inc'
c
C------ External Declarations --------------------------------------------------
c
	INTEGER Boptn, Wbank, VTXinit, Blocat, Wdata, Trkdtfs
	INTEGER Bnext, Blist, Bdrop, Wdrop
c
c------ Local Declarations -----------------------------------------------------
c
	INTEGER Istat, i, Ind, Indtfs, Dimvwrk, nfittr, vwrkhsiz
	CHARACTER*80 Message
c
c====== Start of executable Code ===============================================
c
c=============================================================================
c (1) General initialization
c=============================================================================
c
c --- Initialize parameters ---
c
        TOTTRK = 0
c
c --- Number of fitted tracks from DCHD ---
c
	ISTAT = BLOCAT(IW,'DCHD',-1,IND,INDTFS)
        if ( ISTAT.ne.YESUCC ) then
           message = 'No DGHD bank found'
           call ERLOGR('VTXFIN_EV',ERWARN,0,0,message)
           return
        endif
	nfittr = IW(INDTFS+IW(INDTFS+DCHHDS)+DCHTRK)
c
c --- Locate DTFS banks ---
c
        ISTAT = BLOCAT(IW,'DTFS',-1,IND,INDTFS)
        if ( ISTAT.ne.YESUCC ) then
           message = 'No DTFS bank found'
           call ERLOGR('VTXFIN_EV',ERWARN,0,0,message)
           return
        endif
c
c --- Create work bank ---
c 1- Index IVWRK is returned by WBANK as VWRK bank index
c 2- The call to BOPTN zeros all bank elements
c 3- The header size of a work bank is always 4 (see appendix B of YBOS man.)
c
	IVWRK = 0
	vwrkhsiz = 4
        ISTAT = BOPTN(IW,0)
	DIMVWRK = VWRNCO * nfittr + vwrkhsiz
	ISTAT = WBANK(IW,IVWRK,DIMVWRK)
           if ( ISTAT.ne.YESUCC ) then
              message = 'Error while creating work bank'
              call ERLOGR('VTXFIN_EV',ERWARN,0,0,message)
              return
           endif
	ISTAT = WDATA(IW,IVWRK,INDVWRK)
c
c --- Start loop on tracks ---
c
 111	continue
	TOTTRK  = TOTTRK + 1
c
c check that total number of tracks is note greater than DCHD number
c
	if ( tottrk .gt. nfittr ) then
	   message = 'More DTFS banks exist than expected from DCHD!?'
	   call ERLOGR('VTXFIN_EV',ERWARN,0,0,message)
	   return
        endif
	TRKDTFS = IW(IND-2)    ! DTFS track number
c
c --- Fill work bank and extrapolate track  ---
c
        ISTAT = VTXINIT(TOTTRK,TRKDTFS)
           if ( ISTAT.ne.YESUCC ) then
              message = 'Error while initializing track'
              call ERLOGR('VTXFIN_EV',ERWARN,0,0,message)
              TOTTRK = TOTTRK - 1
           endif
c
	ISTAT = BNEXT(IW,IND,IND)
	if (IND.gt.0) goto 111
c
c End of loop on tracks
c
c=============================================================================
c (2) Vertex fit
c=============================================================================
c
c --- Start vertex search ---
c
	call VTXFIT
c
c=============================================================================
c (3) Output section
c=============================================================================
c
c --- Classify vertices and write output bank (DVFS) ---
c
	if ( NVXFIT .gt. 0 )	call VTXMERG
c
c ---  Now drop work bank and save banks needed to be saved ---
c
	istat = WDROP(IW,IVWRK,1)
	IF( istat.ne.YESUCC ) THEN
              message = 'Error while dropping work bank'
	      call ERLOGR ('VTXFIN_EV',ERWARN,0,0,message)
	ENDIF
c
	if ( NVXFIT .gt. 0) then
	   istat = BLIST(IW,'A+','DVFS')
	   IF( istat.ne.YESUCC ) THEN
              message = 'Error in adding DVFS to A list'
	      call ERLOGR ('VTXFIN_EV',ERWARN,0,0,message)
	   ENDIF
	endif
C       
999	return
	end

[KLOE] [Offline Doc] [TRK Files]
Generated with Light on Thu Apr 8 13:00:16 MET DST 1999 .
Mail comments and suggestions.