C =================================================================
C ATFMOD - Normal Module for the ARGUS track fit algorithm for KLOE
C =================================================================
C
C Language:-
C ==========
C KLOE Fortran
C
C Modulename:-
C ============
C ATFMOD.KLOE
C
C Description:-
C =============
C This is an A_C Normal Module which contains all entries to run
C the charged track reconstruction program in the A_C environment.
C
C ATFINI Initialize input program at start of job.
C ATFRIN Run Initialization Entry.
C ATFEVT Event Entry.
C ATFRFI Run End Entry.
C ATFFIN Cleanup for job termination.
C ATFBOO Histogram/ntuple booking
C ATFTLK Talk module
C
C Author:-
C ========
C F. Donno & F. Pelucchi
C KLOE Computing Group
C LNF Frascati
C
C Revision History:-
C ==================
C 19 Oct 1993 Original Creation
C (from the original program MAINGAINT.FOR by Alexander Andryakov)
C 11 Oct 1994 Updated by A. Andryakov
C
SUBROUTINE ATFINI
C =================
$$IMPLICIT
C
C Description:-
C =============
C This routine is called at program initialisation time.
C It sets two main control flags, and then
C fills up the /ATFTALK/ common with talk_to menu information.
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C None
C
C Global Declarations:-
C =====================
C
$$INCLUDE 'S_I$LIBRARY:NOARGINC.INC'
$$INCLUDE 'K$ITRK:CFLAGS.INC'
C
C External reference (block data)
C ===============================
EXTERNAL BLKDAT
C
INTEGER GROUP,MENUID1,MENUID2,MENUID3
COMMON /ATFTALK/ GROUP,MENUID1,MENUID2,MENUID3
C
C External Functions:-
C ====================
INTEGER UIDFFI
C
C
C Local Declarations:-
C ====================
INTEGER STATUS
C
C Executable Code:-
C =================
C
C The Default operation mode is to run the track fit
C
TRACK_FIT = .TRUE.
KINK_RECO = .TRUE.
MUSC = .TRUE.
DEDX = .TRUE.
JOIN = .TRUE.
C
C Read ATFTLK Definition File
C ===========================
STATUS = UIDFFI('K$TRK:ATFTLK.UID',GROUP,MENUID1,
& N$A,N$A,MENUID3,N$A)
IF (MENUID3.GT.MENUID1) THEN
MENUID2=MENUID1+1
ENDIF
C
RETURN
END
C
SUBROUTINE ATFRIN
C =================
$$IMPLICIT
C
C Description:-
C =============
C This routine is called at run initialisation time.
C No actions at present
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C None
C
C
C Global Declarations:-
C =====================
C
C
C External Functions:-
C ====================
C
C
C Local Declarations:-
C ====================
C
C
C Executable Code:-
C =================
C
RETURN
END
C
SUBROUTINE ATFEVT
C =================
$$IMPLICIT
C
C Description:-
C =============
C This routine calls track reconstruction
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C None
C
C Global Declarations:-
C =====================
C
$$INCLUDE 'K$INC:BCS.INC'
$$INCLUDE 'K$INC:BPOYBS.INC'
$$INCLUDE 'K$INC:JOBSTA.INC'
$$INCLUDE 'K$INC:ERLEVL.INC'
$$INCLUDE 'YBOS$LIBRARY:ERRCOD.INC'
$$INCLUDE 'K$ITRK:CFLAGS.INC'
C
C External Functions:-
C ====================
C
INTEGER BLOCAT,BLIST,BDROP
C
C Local Declarations:-
C ====================
C
INTEGER STATUS,IND,INDDAT
INTEGER SEED1,SEED2
C
C Executable Code:-
C =================
C
C These may be useful here ?
STATUS = BLOCAT(IW,'HEAD',1,IND,INDDAT)
IF (STATUS.EQ.YESUCC) THEN
SEED1 = IW(INDDAT+HEARND)
SEED2 = IW(INDDAT+HEARND+1)
ELSE
ENDIF
C
C Track fit will now be performed
C ===============================
IF (TRACK_FIT) THEN
STATUS = BDROP(IW,'DTFS')
STATUS = BDROP(IW,'DHSP')
C
C Before starting, check for existence of DHRE.
STATUS = BLOCAT(IW,'DHRE',1,IND,INDDAT)
IF (STATUS.NE.YESUCC) RETURN
C
CALL DFMAIN
C
STATUS = BLIST(IW,'A+','DTFS')
IF (STATUS .NE. YESUCC) THEN
CALL ERLOGR('ATFEVT',ERWARN,0,STATUS,
& 'DTFS banks not added to A list')
ENDIF
ENDIF
C
RETURN
END
C
SUBROUTINE ATFRFI
C =================
C
C Description:-
C =============
C This routine is called at run termination.
C It does any necessary cleanup.
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C None
C
C
C Global Declarations:-
C =====================
C
$$IMPLICIT
C
C External Functions:-
C ====================
C
C Local Declarations:-
C ====================
C
C For now, this is a noopt!!!
C
RETURN
END
C
C
SUBROUTINE ATFFIN
C =================
C
C Description:-
C =============
C This routine is called at program termination.
C It does any necessary cleanup.
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C None
C
C
C Global Declarations:-
C =====================
C
$$IMPLICIT
C
C External Functions:-
C ====================
C
C Local Declarations:-
C ====================
C
C For now, this is a noopt!!!
C
RETURN
END
C
SUBROUTINE ATFBOO
C =================
C
C Description:-
C =============
C This routine is called at run initialisation.
C It books the histograms and ntuple
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C
C
C
C Global Declarations:-
C =====================
C
$$IMPLICIT
C
C External Functions:-
C ====================
C
C Local Declarations:-
C ====================
C
C Executable Code:-
C =================
C
CALL HBOOK1(1,'Initial n. of hits/candidate$',100,0.,100.,0.)
CALL HBOOK1(2,'N.of additional hits/track$',100,0.,100.,0.)
CALL HBOOK1(3,'N.of rejected hits/track$',100,0.,100.,0.)
CALL HBOOK1(4,'N.of hits/fitted track$',100,0.,100.,0.)
CALL HBOOK1(5,'Number of fitted tracks$',20,0.,20.,0.)
CALL HBOOK1(6,'Number of fitted tracks from IP$',20,0.,20.,0.)
CALL HBOOK1(7,'Unassociated hits after TF recovering$',
. 100,0.,100.,0.)
CALL HBOOK1(8,'Fraction of unass.hits after TF recovering$',
. 50,0.,1.,0.)
CALL HBOOK1(9,'Chi2/ndgf$',50,0.,10.,0.)
CALL HBOOK1(10,'Chi2 probability$',51,0.,1.02,0.)
CALL HBOOK1(11,'N.of hits (failed fits)$',100,0.,100.,0.)
CALL HBOOK1(12,'Error codes (failed fits)$',50,0.,50.,0.)
CALL HBOOK1(13,'2D step length from PR',100,-100.,100.,0.)
CALL HBOOK1(14,'old step length',100,-100.,100.,0.)
CALL HBOOK1(15,'new step length',100,-100.,100.,0.)
CALL HBOOK1(16,'N.of hits (successful fits)$',100,0.,100.,0.)
CALL HBOOK1(17,'Error codes (successful fits)$',50,0.,50.,0.)
CALL HBOOK1(20,'Chi2/ndgf$',100,0.,1000.,0.)
CALL HBOOK1(21,'Chi2/ndgf$',100,0.,1000.,0.)
CALL HBOOK1(22,'Chi2/ndgf$',100,0.,1000.,0.)
c
CALL HBOOK2(61,'Extrap. R0/Z0, inner tracks',
. 50,-50.,50.,50,0.,50.,0.)
CALL HBOOK2(62,'Extrap. R0/Z0, outer tracks',
. 50,-50.,50.,50,0.,50.,0.)
C
CALL HBOOK1(71,'DFKINK exit codes',10,50.,1050.,0.)
CALL HBOOK1(72,'Kink position',200,0.,200.,0.)
CALL HBOOK1(400,'Track fit INERR codes',100,0.,100.,0.)
CALL HBOOK1(408,'aborted-worse chi2-OK$',
+ 10,0.,10.,0.)
CALL HBOOK1(409,'Delta-chi2$',
+ 100,-50.,50.,0.)
CALL HBOOK1(415,' DFirst-last, trk pairs $',
+ 100,0.,100.,0.)
CALL HBOOK1(416,' Parall., trk pairs - all pairs$',
+ 100,-1.,1.,0.)
CALL HBOOK1(417,' Parall., trk pairs - close pairs$',
+ 100,-1.,1.,0.)
CALL HBOOK2(418,' Or1+Or2 - Close pairs, antiparallel$',
+ 100,-0.2,0.2,100,-1.,1.,0.)
c
CALL HBOOK1(450,'Residuals in units of d.d. error',
+ 100,-10.,10.,0.)
C
CALL HBPRO(0,0.)
C
RETURN
END
C
SUBROUTINE ATFTLK
C =================
$$IMPLICIT
C
C Description:-
C =============
C This talk_to routine prompts the User to choose the number
C which determines a good event.
C
C Call Parameters:-
C ================
C None
C
C Return Parameters:-
C ===================
C None
C
C Function Value:-
C ================
C None
C
C
C Global Declarations:-
C =====================
C
$$INCLUDE 'K$ITRK:CFLAGS.INC'
$$INCLUDE 'K$ITRK:CDFCUT.INC'
$$INCLUDE 'UIPACK$LIBRARY:UIERROR.INC'
$$INCLUDE 'S_I$LIBRARY:NOARGINC.INC'
C
INTEGER GROUP,MENUID1,MENUID2,MENUID3
COMMON /ATFTALK/ GROUP,MENUID1,MENUID2,MENUID3
C
C External Declarations:-
C =======================
C
INTEGER UIUSGP,UIACME,UIGTYE,UIGTIN,UIGTRE
C
C Local Declarations:-
C ====================
C
INTEGER STATUS
CHARACTER*40 VERB
C
C Executable Code:-
C =================
C
C Loop over "mode" menu items
C
1000 CONTINUE
STATUS = UIUSGP(GROUP,N$A)
STATUS = UIACME(MENUID1,VERB,N$A)
IF (STATUS.EQ.UIABRT) RETURN
C
C Process the TRKF choice
C =======================
IF (VERB.EQ.'TRKF') THEN
STATUS = UIGTYE(
& 'Do you want to perform track fitting?(yes/no)',
& TRACK_FIT)
IF (TRACK_FIT) THEN
ELSE
VERT_FIT = .FALSE.
ENDIF
C
C Process the RJCT choice
C =========================
ELSEIF (VERB.EQ.'RJCT') THEN
STATUS = UIGTIN(
& 'Don''t/do activate hit rejection? (-1/0)',
& LDFREJ,N$A,N$A)
C
C Process the HADD choice
C =========================
ELSEIF (VERB.EQ.'HADD') THEN
STATUS = UIGTIN(
& 'Don''t/do activate hit addition? (-1/0)',
& LDFADD,N$A,N$A)
C
C Process the FNTS choice
C =========================
ELSEIF (VERB.EQ.'FNTS') THEN
STATUS = UIGTYE(
& 'FINE T-s relations used (Yes) / (No) ',
& TS_FINEREL)
IF (TS_FINEREL) TS_RAWREL = .TRUE.
C
C Process the PMKF choice
C =======================
ELSE IF (VERB.EQ.'PMKF') THEN
STATUS = UIGTYE(
& 'Try to recognize p-mu dekay kinks? (yes/no)',
& KINK_RECO)
C
C Process the MSFL choice
C =======================
ELSE IF (VERB.EQ.'MSFL') THEN
STATUS = UIGTYE(
& 'Track fit treats multiple scattering in DC? (yes/no)',
& musc)
IF(musc) THEN
LDFMUS=0
ELSE
LDFMUS=-1
ENDIF
C
C Process the ITER choice
C =========================
ELSE IF (VERB.EQ.'ITER') THEN
STATUS = UIGTIN(
& 'Specify the max number of iterations in DFITER',
& LDFITE,N$A,N$A)
C
C Process the DDER choice
C =========================
ELSE IF (VERB.EQ.'DDER') THEN
STATUS = UIGTRE(
& 'D.distance error (no t->s relations) (cm)',
& DRFDER,N$A,N$A)
C
C Process the DEDX choice
C =========================
ELSE IF (VERB.EQ.'DEDX') THEN
STATUS = UIGTYE(
& 'Use the energy loss in DC? (yes/no)',
& dedx)
IF(dedx) THEN
LDFDX=0
ELSE
LDFDX=-1
ENDIF
C
C Process the TCKJOIN choice
C =========================
ELSE IF (VERB.EQ.'TCKJOIN') THEN
STATUS = UIGTYE(
& 'Use the joining of tracks in DC? (yes/no)',
& join)
IF(join) THEN
LDFJOI=0
ELSE
LDFJOI=-1
ENDIF
C
C Process the TFLOAD choice
C =======================
ELSE IF (VERB.EQ.'TFLOAD') THEN
LDFREJ = 0
LDFADD = 0
TS_FINEREL = .TRUE.
KINK_RECO = .TRUE.
LDFMUS = 0
LDFITE = 8
DRFDER = 0.0200
LDFDX = 0
LDFJOI = 0
C
C Process the RETURN choice
C =========================
ELSE IF(VERB.EQ.'RETURN') THEN
RETURN
ENDIF
C
GOTO 1000
C
END
C
[KLOE]
[Offline Doc]
[TRK Files]
Generated with Light on Thu Apr 8 13:00:16 MET DST 1999
.
Mail comments and suggestions.