+++ /dev/null
-*CMZ : 02/02/99 18.09.13 by Federico Carminati
-*-- Author : Federico Carminati 02/02/99
- SUBROUTINE GFLUCT(DEMEAN,DE)
-C.
-C. ******************************************************************
-C. * *
-C. * Subroutine to decide which method is used to simulate *
-C. * the straggling around the mean energy loss. *
-C. * *
-C. * *
-C. * DNMIN: <---------->1<-------->30<--------->50<---------> *
-C. * *
-C. * LOSS=2 : *
-C. * STRA=0 <----------GLANDZ-------------------><--GLANDO--> *
-C. * LOSS=1,3: *
-C. * STRA=0 <---------------------GLANDZ--------------------> *
-C. * *
-C. * STRA=1 <-----------PAI---------------------><--GLANDZ--> *
-C. * *
-C. * DNMIN : an estimation of the number of collisions *
-C. * with energy close to the ionization energy *
-C. * (see PHYS333) *
-C. * *
-C. * Input : DEMEAN (mean energy loss) *
-C. * Output : DE (energy loss in the current step) *
-C. * *
-C. * ==>Called by : GTELEC,GTMUON,GTHADR *
-C. * *
-C. ******************************************************************
-C.
-#include "geant321/pilot.h"
-#undef CERNLIB_GEANT321_GCBANK_INC
-#undef CERNLIB_GEANT321_GCLINK_INC
-#include "geant321/gcbank.inc"
-#undef CERNLIB_GEANT321_GCJLOC_INC
-#include "geant321/gcjloc.inc"
-#undef CERNLIB_GEANT321_GCONSP_INC
-#include "geant321/gconsp.inc"
-#undef CERNLIB_GEANT321_GCMATE_INC
-#include "geant321/gcmate.inc"
-#undef CERNLIB_GEANT321_GCCUTS_INC
-#include "geant321/gccuts.inc"
-#undef CERNLIB_GEANT321_GCKINE_INC
-#include "geant321/gckine.inc"
-#undef CERNLIB_GEANT321_GCMULO_INC
-#include "geant321/gcmulo.inc"
-#undef CERNLIB_GEANT321_GCPHYS_INC
-#include "geant321/gcphys.inc"
-#undef CERNLIB_GEANT321_GCTRAK_INC
-#include "geant321/gctrak.inc"
-*KEND.
- PARAMETER (EULER=0.577215,GAM1=EULER-1)
- PARAMETER (P1=.60715,P2=.67794,P3=.52382E-1,P4=.94753,
- + P5=.74442,P6=1.1934)
- PARAMETER (DGEV=0.153536 E-3, DNLIM=50)
-* These parameters are needed by M.Kowalski's fluctuation algorithm
- PARAMETER (FPOT=20.77E-9, EEND=10E-6, EEXPO=2.2)
- PARAMETER (XEXPO=-EEXPO+1, YEXPO=1/XEXPO)
-* These parameters are needed by M.Kowalski's fluctuation algorithm
- DIMENSION RNDM(2)
- DE2(DPOT,RAN)=(DPOT**XEXPO*(1-RAN)+EEND**XEXPO*RAN)**YEXPO
- FLAND(X) = P1+P6*X+(P2+P3*X)*EXP(P4*X+P5)
- IF(STEP.LE.0) THEN
- DE=DEMEAN
- ELSE
- DEDX = DEMEAN/STEP
- POTI=Q(JPROB+9)
- IF(ISTRA.EQ.0.AND.(ILOSS.EQ.1.OR.ILOSS.EQ.3)) THEN
- CALL GLANDZ(Z,STEP,VECT(7),GETOT,DEDX,DE,POTI,Q(JPROB+10))
- ELSEIF (ILOSS.EQ.5) THEN
-* This is Marek Kowalski's fluctuation algorithm, it works only when
-* the step size has been limited to one ionisation on average
- CALL GRNDM(RNDM,1)
- DE=DE2(FPOT,RNDM(1))
-*
- ELSE
-* *** mean ionization potential (GeV)
-* POTI=16E-9*Z**0.9
- GAMMA = GETOT/AMASS
- BETA = VECT(7)/GETOT
- BET2 = BETA**2
-* *** low energy transfer
- XI = DGEV*CHARGE**2*STEP*DENS*Z/(A*BET2)
-* *** regime
-* *** ISTRA = 1 --> PAI + URBAN
- DNMIN = MIN(XI,DEMEAN)/POTI
- IF (ISTRA.EQ.0) THEN
- IF(DNMIN.GE.DNLIM) THEN
-* Energy straggling using Gaussian, Landau & Vavilov theories.
-* STEP = current step-length (cm)
-* DELAND = DE/DX - <DE/DX> (GeV)
-* Author : G.N. Patrick
- IF(STEP.LT.1.E-7)THEN
- DELAND=0.
- ELSE
-* Maximum energy transfer to atomic electron (GeV).
- ETA = BETA*GAMMA
- RATIO = EMASS/AMASS
-* Calculate Kappa significance ratio.
-* EMAX=(2*EMASS*ETA**2)/(1+2*RATIO*GAMMA+RATIO**2)
-* CAPPA = XI/EMAX
- CAPPA = XI*(1+2*RATIO*GAMMA+RATIO**2)/(2*EMASS*
- + ETA**2)
- IF (CAPPA.GE.10.) THEN
-* +-----------------------------------+
-* I Sample from Gaussian distribution I
-* +-----------------------------------+
- SIGMA = XI*SQRT((1.-0.5*BET2)/CAPPA)
- CALL GRNDM(RNDM,2)
- F1 = -2.*LOG(RNDM(1))
- DELAND = SIGMA*SQRT(F1)*COS(TWOPI*RNDM(2))
- ELSE
- XMEAN = -BET2-LOG(CAPPA)+GAM1
- IF (CAPPA.LT.0.01) THEN
- XLAMX = FLAND(XMEAN)
-* +---------------------------------------------------------------+
-* I Sample lambda variable from Kolbig/Schorr Landau distribution I
-* +---------------------------------------------------------------+
-* 10 CALL GRNDM(RNDM,1)
-* IF( RNDM(1) .GT. 0.980 ) GO TO 10
-* XLAMB = GLANDR(RNDM(1))
-* +---------------------------------------------------------------+
-* I Sample lambda variable from James/Hancock Landau distribution I
-* +---------------------------------------------------------------+
- 10 CALL GLANDG(XLAMB)
- IF(XLAMB.GT.XLAMX) GO TO 10
- ELSE
-* +---------------------------------------------------------+
-* I Sample lambda variable (Landau not Vavilov) from I
-* I Rotondi&Montagna&Kolbig Vavilov distribution I
-* +---------------------------------------------------------+
- CALL GRNDM(RNDM,1)
- XLAMB = GVAVIV(CAPPA,BET2,RNDM(1))
- ENDIF
-* Calculate DE/DX - <DE/DX>
- DELAND = XI*(XLAMB-XMEAN)
- ENDIF
- ENDIF
- DE = DEMEAN + DELAND
- ELSE
- CALL GLANDZ(Z,STEP,VECT(7),GETOT,DEDX,DE,POTI,
- + Q(JPROB+ 10))
- ENDIF
- ELSE IF (ISTRA.LE.2) THEN
- IF(DNMIN.GE.DNLIM) THEN
- CALL GLANDZ(Z,STEP,VECT(7),GETOT,DEDX,DE,POTI,
- + Q(JPROB+ 10))
- ELSE
- NMEC = NMEC+1
- LMEC(NMEC)=109
- DE = GSTREN(GAMMA,DCUTE,STEP)
-* *** Add brem losses to ionisation
- IF(ITRTYP.EQ.2) THEN
- JBASE = LQ(JMA-1)+2*NEK1+IEKBIN
- DE = DE +(1.-GEKRAT)*Q(JBASE)+GEKRAT*Q(JBASE+1)
- ELSEIF(ITRTYP.EQ.5) THEN
- JBASE = LQ(JMA-2)+NEK1+IEKBIN
- DE = DE +(1.-GEKRAT)*Q(JBASE)+GEKRAT*Q(JBASE+1)
- ENDIF
- ENDIF
- ENDIF
- ENDIF
- ENDIF
- END
-*CMZ : 16/02/99 19.24.38 by Federico Carminati
-*CMZ : 2.03/01 28/08/98 09.33.11 by Federico Carminati
-*CMZ : 2.01/00 18/06/98 17.34.13 by Federico Carminati
-*CMZ : 2.00/05 28/05/98 19.04.13 by Federico Carminati
-*-- Author :
- SUBROUTINE GTREVE
-C.
-C. ******************************************************************
-C. * *
-C. * SUBR. GTREVE *
-C. * *
-C. * Controls tracking of all particles belonging to the current *
-C. * event. *
-C. * *
-C. * Called by : GUTREV, called by GTRIG *
-C. * Authors : R.Brun, F.Bruyant *
-C. * *
-C. ******************************************************************
-C.
-#include "geant321/pilot.h"
-#undef CERNLIB_GEANT321_GCBANK_INC
-#undef CERNLIB_GEANT321_GCLINK_INC
-#include "geant321/gcbank.inc"
-#undef CERNLIB_GEANT321_GCFLAG_INC
-#include "geant321/gcflag.inc"
-#undef CERNLIB_GEANT321_GCKINE_INC
-#include "geant321/gckine.inc"
-#undef CERNLIB_GEANT321_GCNUM_INC
-#include "geant321/gcnum.inc"
-#undef CERNLIB_GEANT321_GCSTAK_INC
-#include "geant321/gcstak.inc"
-#undef CERNLIB_GEANT321_GCTMED_INC
-#include "geant321/gctmed.inc"
-#undef CERNLIB_GEANT321_GCTRAK_INC
-#include "geant321/gctrak.inc"
-#undef CERNLIB_GEANT321_GCUNIT_INC
-#include "geant321/gcunit.inc"
-#include "sckine.inc"
-*KEND.
-*
- REAL UBUF(2)
- EQUIVALENCE (UBUF(1),WS(1))
- LOGICAL BTEST
- DIMENSION PMOM(3),VPOS(3)
-C.
-C. ------------------------------------------------------------------
- NTMSTO = 0
- NSTMAX = 0
- NALIVE = 0
-* Kick start the creation of the vertex
- VPOS(1)=0
- VPOS(2)=0
- VPOS(3)=0
- PMOM(1)=0
- PMOM(2)=0
- PMOM(3)=0
- IPART=1
- CALL GSVERT(VPOS,0,0,UBUF,0,NVTX)
- CALL GSKINE(PMOM,IPART,NVTX,UBUF,0,NT)
-*
- MTRACK=-999
- 10 MTROLD=MTRACK
- CALL RXGTRAK(MTRACK,IPART,PMOM,E,VPOS,TTOF)
- IF(MTROLD.LT.0) THEN
- MPRIMA=MTRACK
- ENDIF
- IF(MTRACK.LE.MPRIMA) THEN
- IF(ISWIT(4).GT.0.AND.MTRACK.GT.0) THEN
- IF(ISWIT(4).EQ.1.OR.MOD(MTRACK,ISWIT(4)).EQ.0) THEN
- WRITE(CHMAIL,10200) MTRACK
- CALL GMAIL(0,0)
- ENDIF
- ENDIF
- IF(MTROLD.GT.0) THEN
-C --- Output root hits tree only for each primary MTRACK
- CALL RXOUTH
- ENDIF
- ENDIF
- IF(MTRACK.LE.0) GOTO 999
-* Set the vertex
- JV=LQ(JVERTX-1)
- Q(JV + 1) = VPOS(1)
- Q(JV + 2) = VPOS(2)
- Q(JV + 3) = VPOS(3)
- Q(JV + 4) = TTOF
- Q(JV + 5) = 0
- Q(JV + 6) = 0
-* Set the track
- JK=LQ(JKINE-1)
- Q(JK + 1) = PMOM(1)
- Q(JK + 2) = PMOM(2)
- Q(JK + 3) = PMOM(3)
- Q(JK + 4) = E
- Q(JK + 5) = IPART
- Q(JK + 6) = 1
-* Now transport
-C CALL GPVERT(0)
-C CALL GPKINE(0)
-* Normal Gtreve code
- NV = NVERTX
- DO 40 IV = 1,NV
-* *** For each vertex in turn ..
- JV = LQ(JVERTX-IV)
- NT = Q(JV+7)
- IF (NT.LE.0) GO TO 40
- TOFG = Q(JV+4)
- SAFETY = 0.
- IF (NJTMAX.GT.0) THEN
- CALL GMEDIA (Q(JV+1), NUMED)
- IF (NUMED.EQ.0) THEN
- WRITE (CHMAIL, 10000) (Q(JV+I), I=1,3)
- CALL GMAIL (0, 0)
- GO TO 40
- ENDIF
- CALL GLSKLT
- ENDIF
-* ** Loop over tracks attached to current vertex
- DO 20 IT = 1,NT
- JV = LQ(JVERTX-IV)
- ITRA = Q(JV+7+IT)
- IF (BTEST(IQ(LQ(JKINE-ITRA)),0)) GO TO 20
- CALL GFKINE (ITRA, VERT, PVERT, IPART, IVERT, UBUF, NWBUF)
- IF (IVERT.NE.IV) THEN
- WRITE (CHMAIL, 10100) IV, IVERT
- CALL GMAIL (0, 0)
- GO TO 999
- ENDIF
-* * Store current track parameters in stack JSTAK
- CALL GSSTAK (2)
- 20 CONTINUE
-* ** Start tracking phase
- 30 IF (NALIVE.NE.0) THEN
- NALIVE = NALIVE -1
-* * Pick-up next track in stack JSTAK, if any
-* * Initialize tracking parameters
- CALL GLTRAC
- IF (NUMED.EQ.0) GO TO 30
-* * Resume tracking
- CALL GUTRAK
- IF (IEOTRI.NE.0) GO TO 999
- GO TO 30
- ENDIF
-*
- 40 CONTINUE
- GOTO 10
-*
-10000 FORMAT (' GTREVE : Vertex outside setup, XYZ=',3G12.4)
-10100 FORMAT (' GTREVE : Abnormal track/vertex connection',2I8)
-10200 FORMAT (' GTREVE : Transporting primary track No ',I10)
-* END GTREVE
- 999 END
# DO NOT DELETE THIS LINE -- make depend depends on it.
TGeant3.o: TGeant3.h /hdb2/offline/pro/include/AliMC.h
-TGeant3.o: /soft/root/include/TNamed.h /soft/root/include/TObject.h
-TGeant3.o: /soft/root/include/Rtypes.h /soft/root/include/RConfig.h
-TGeant3.o: /usr/include/stdio.h /usr/local/include/g++/libio.h
-TGeant3.o: /usr/include/_G_config.h /usr/include/gnu/types.h
+TGeant3.o: /soft/root/include/TNamed.h /soft/root/include/TROOT.h THIGZ.h
+TGeant3.o: /soft/root/include/TCanvas.h /usr/include/ctype.h
TGeant3.o: /usr/include/features.h /usr/include/sys/cdefs.h
-TGeant3.o: /usr/include/gnu/stubs.h
-TGeant3.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stddef.h
-TGeant3.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stdarg.h
-TGeant3.o: /usr/include/stdio_lim.h /soft/root/include/DllImport.h
-TGeant3.o: /soft/root/include/Varargs.h /soft/root/include/TStorage.h
-TGeant3.o: /soft/root/include/TBuffer.h /usr/include/string.h
-TGeant3.o: /soft/root/include/Bytes.h /soft/root/include/TList.h
-TGeant3.o: /soft/root/include/TSeqCollection.h
-TGeant3.o: /soft/root/include/TCollection.h /soft/root/include/TIterator.h
-TGeant3.o: /soft/root/include/TString.h /soft/root/include/TMath.h
-TGeant3.o: /soft/root/include/TRefCnt.h /soft/root/include/TROOT.h
-TGeant3.o: /soft/root/include/TDirectory.h /soft/root/include/TDatime.h
-TGeant3.o: /soft/root/include/Htypes.h THIGZ.h /soft/root/include/TCanvas.h
-TGeant3.o: /soft/root/include/TPad.h /soft/root/include/TVirtualPad.h
-TGeant3.o: /soft/root/include/TAttPad.h /soft/root/include/Gtypes.h
-TGeant3.o: /soft/root/include/TFrame.h /soft/root/include/TWbox.h
-TGeant3.o: /soft/root/include/TBox.h /soft/root/include/TAttLine.h
-TGeant3.o: /soft/root/include/TAttFill.h /soft/root/include/TGXW.h
-TGeant3.o: /soft/root/include/TAttText.h /soft/root/include/TAttMarker.h
-TGeant3.o: /soft/root/include/GuiTypes.h /soft/root/include/Buttons.h
-TGeant3.o: /soft/root/include/TAttCanvas.h /soft/root/include/TCanvasImp.h
-TGeant3.o: /usr/include/ctype.h /usr/include/endian.h /usr/include/bytesex.h
-TGeant3.o: /hdb2/offline/pro/include/AliCallf77.h
+TGeant3.o: /usr/include/gnu/stubs.h /usr/include/endian.h
+TGeant3.o: /usr/include/bytesex.h /hdb2/offline/pro/include/AliCallf77.h
TPaveTree.o: /usr/local/include/g++/fstream.h
TPaveTree.o: /usr/local/include/g++/iostream.h
TPaveTree.o: /usr/local/include/g++/streambuf.h
TPaveTree.o: /usr/include/sys/cdefs.h /usr/include/gnu/stubs.h
TPaveTree.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stddef.h
TPaveTree.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stdarg.h
-TPaveTree.o: /soft/root/include/TROOT.h /soft/root/include/TDirectory.h
-TPaveTree.o: /soft/root/include/TDatime.h /soft/root/include/Htypes.h
-TPaveTree.o: /soft/root/include/TVirtualPad.h /soft/root/include/TAttPad.h
-TPaveTree.o: /soft/root/include/Gtypes.h /soft/root/include/TFrame.h
-TPaveTree.o: /soft/root/include/TWbox.h /soft/root/include/TBox.h
-TPaveTree.o: /soft/root/include/TAttLine.h /soft/root/include/TAttFill.h
-TPaveTree.o: /soft/root/include/TGXW.h /soft/root/include/TAttText.h
-TPaveTree.o: /soft/root/include/TAttMarker.h /soft/root/include/GuiTypes.h
+TPaveTree.o: /soft/root/include/TROOT.h /soft/root/include/TVirtualPad.h
TPaveTree.o: /soft/root/include/Buttons.h TPaveTree.h
-TPaveTree.o: /soft/root/include/TPaveLabel.h /soft/root/include/TPave.h
-TPaveTree.o: /soft/root/include/TString.h /usr/include/string.h
-TPaveTree.o: /soft/root/include/TMath.h /soft/root/include/TRefCnt.h
-TPaveTree.o: TGeant3.h /hdb2/offline/pro/include/AliMC.h
-TPaveTree.o: /soft/root/include/TNamed.h /soft/root/include/TObject.h
-TPaveTree.o: /soft/root/include/Rtypes.h /soft/root/include/RConfig.h
-TPaveTree.o: /usr/include/stdio.h /usr/include/stdio_lim.h
-TPaveTree.o: /soft/root/include/DllImport.h /soft/root/include/Varargs.h
-TPaveTree.o: /soft/root/include/TStorage.h /soft/root/include/TBuffer.h
-TPaveTree.o: /soft/root/include/Bytes.h /soft/root/include/TList.h
-TPaveTree.o: /soft/root/include/TSeqCollection.h
-TPaveTree.o: /soft/root/include/TCollection.h /soft/root/include/TIterator.h
-THIGZ.o: /soft/root/include/TROOT.h /soft/root/include/TDirectory.h
-THIGZ.o: /soft/root/include/TDatime.h /soft/root/include/Htypes.h THIGZ.h
-THIGZ.o: /soft/root/include/TCanvas.h /soft/root/include/TPad.h
-THIGZ.o: /soft/root/include/TVirtualPad.h /soft/root/include/TAttPad.h
-THIGZ.o: /soft/root/include/Gtypes.h /soft/root/include/TFrame.h
-THIGZ.o: /soft/root/include/TWbox.h /soft/root/include/TBox.h
-THIGZ.o: /soft/root/include/TAttLine.h /soft/root/include/TAttFill.h
-THIGZ.o: /soft/root/include/TGXW.h /soft/root/include/TAttText.h
-THIGZ.o: /soft/root/include/TAttMarker.h /soft/root/include/GuiTypes.h
-THIGZ.o: /soft/root/include/Buttons.h /soft/root/include/TAttCanvas.h
-THIGZ.o: /soft/root/include/TCanvasImp.h TGeant3.h
-THIGZ.o: /hdb2/offline/pro/include/AliMC.h /soft/root/include/TNamed.h
-THIGZ.o: /soft/root/include/TObject.h /soft/root/include/Rtypes.h
-THIGZ.o: /soft/root/include/RConfig.h /usr/include/stdio.h
-THIGZ.o: /usr/local/include/g++/libio.h /usr/include/_G_config.h
-THIGZ.o: /usr/include/gnu/types.h /usr/include/features.h
+TPaveTree.o: /soft/root/include/TPaveLabel.h TGeant3.h
+TPaveTree.o: /hdb2/offline/pro/include/AliMC.h /soft/root/include/TNamed.h
+THIGZ.o: /soft/root/include/TROOT.h THIGZ.h /soft/root/include/TCanvas.h
+THIGZ.o: TGeant3.h /hdb2/offline/pro/include/AliMC.h
+THIGZ.o: /soft/root/include/TNamed.h /soft/root/include/TGraph.h
+THIGZ.o: /soft/root/include/TColor.h /soft/root/include/TLine.h
+THIGZ.o: /soft/root/include/TPolyLine.h /soft/root/include/TPolyMarker.h
+THIGZ.o: /soft/root/include/TPaveLabel.h /soft/root/include/TText.h
+THIGZ.o: /soft/root/include/Rtypes.h /hdb2/offline/pro/include/AliCallf77.h
+THIGZ.o: TPaveTree.h /usr/include/string.h /usr/include/features.h
THIGZ.o: /usr/include/sys/cdefs.h /usr/include/gnu/stubs.h
THIGZ.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stddef.h
-THIGZ.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stdarg.h
-THIGZ.o: /usr/include/stdio_lim.h /soft/root/include/DllImport.h
-THIGZ.o: /soft/root/include/Varargs.h /soft/root/include/TStorage.h
-THIGZ.o: /soft/root/include/TBuffer.h /usr/include/string.h
-THIGZ.o: /soft/root/include/Bytes.h /soft/root/include/TList.h
-THIGZ.o: /soft/root/include/TSeqCollection.h /soft/root/include/TCollection.h
-THIGZ.o: /soft/root/include/TIterator.h /soft/root/include/TString.h
-THIGZ.o: /soft/root/include/TMath.h /soft/root/include/TRefCnt.h
-THIGZ.o: /soft/root/include/TGraph.h /soft/root/include/TColor.h
-THIGZ.o: /soft/root/include/TLine.h /soft/root/include/TPolyLine.h
-THIGZ.o: /soft/root/include/TPolyMarker.h /soft/root/include/TPaveLabel.h
-THIGZ.o: /soft/root/include/TPave.h /soft/root/include/TText.h
-THIGZ.o: /hdb2/offline/pro/include/AliCallf77.h TPaveTree.h
THIGZ.o: /usr/include/ctype.h /usr/include/endian.h /usr/include/bytesex.h
gucode.o: /hdb2/offline/pro/include/AliCallf77.h TGeant3.h
gucode.o: /hdb2/offline/pro/include/AliMC.h /soft/root/include/TNamed.h
-gucode.o: /soft/root/include/TObject.h /soft/root/include/Rtypes.h
-gucode.o: /soft/root/include/RConfig.h /usr/include/stdio.h
-gucode.o: /usr/local/include/g++/libio.h /usr/include/_G_config.h
-gucode.o: /usr/include/gnu/types.h /usr/include/features.h
-gucode.o: /usr/include/sys/cdefs.h /usr/include/gnu/stubs.h
-gucode.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stddef.h
-gucode.o: /usr/local/lib/gcc-lib/i686-pc-linux-gnu/egcs-2.91.60/include/stdarg.h
-gucode.o: /usr/include/stdio_lim.h /soft/root/include/DllImport.h
-gucode.o: /soft/root/include/Varargs.h /soft/root/include/TStorage.h
-gucode.o: /soft/root/include/TBuffer.h /usr/include/string.h
-gucode.o: /soft/root/include/Bytes.h /soft/root/include/TList.h
-gucode.o: /soft/root/include/TSeqCollection.h
-gucode.o: /soft/root/include/TCollection.h /soft/root/include/TIterator.h
-gucode.o: /soft/root/include/TString.h /soft/root/include/TMath.h
-gucode.o: /soft/root/include/TRefCnt.h /hdb2/offline/pro/include/AliRun.h
-gucode.o: /soft/root/include/TROOT.h /soft/root/include/TDirectory.h
-gucode.o: /soft/root/include/TDatime.h /soft/root/include/Htypes.h
-gucode.o: /soft/root/include/TBrowser.h /soft/root/include/TBrowserImp.h
+gucode.o: /hdb2/offline/pro/include/AliRun.h /soft/root/include/TROOT.h
+gucode.o: /soft/root/include/TBrowser.h /soft/root/include/TList.h
gucode.o: /soft/root/include/TStopwatch.h /soft/root/include/TTree.h
-gucode.o: /soft/root/include/TObjArray.h /soft/root/include/TClonesArray.h
-gucode.o: /soft/root/include/TAttLine.h /soft/root/include/TAttFill.h
-gucode.o: /soft/root/include/TAttMarker.h /soft/root/include/TBranch.h
-gucode.o: /soft/root/include/TStringLong.h /soft/root/include/TCut.h
-gucode.o: /soft/root/include/TGeometry.h /soft/root/include/THashList.h
-gucode.o: /hdb2/offline/pro/include/AliModule.h /soft/root/include/TArrayI.h
-gucode.o: /soft/root/include/TArray.h /hdb2/offline/pro/include/AliHit.h
+gucode.o: /soft/root/include/TGeometry.h
+gucode.o: /hdb2/offline/pro/include/AliModule.h
+gucode.o: /soft/root/include/TClonesArray.h /soft/root/include/TAttLine.h
+gucode.o: /soft/root/include/TAttMarker.h /soft/root/include/TArrayI.h
+gucode.o: /hdb2/offline/pro/include/AliHit.h /soft/root/include/TObject.h
gucode.o: /hdb2/offline/pro/include/AliHeader.h
gucode.o: /hdb2/offline/pro/include/AliMagF.h /soft/root/include/TVector.h
-gucode.o: /soft/root/include/TError.h
gucode.o: /hdb2/offline/pro/include/AliGenerator.h
gucode.o: /soft/root/include/TArrayF.h /soft/root/include/TGenerator.h
gucode.o: /hdb2/offline/pro/include/AliLego.h /soft/root/include/TH2.h
-gucode.o: /soft/root/include/TH1.h /soft/root/include/TAxis.h
-gucode.o: /soft/root/include/TAttAxis.h /soft/root/include/Gtypes.h
-gucode.o: /usr/local/include/g++/fstream.h /usr/local/include/g++/iostream.h
-gucode.o: /usr/local/include/g++/streambuf.h /soft/root/include/TLego.h
-gucode.o: /soft/root/include/TF1.h /soft/root/include/TFormula.h
-gucode.o: /soft/root/include/TMethodCall.h /soft/root/include/TGaxis.h
-gucode.o: /soft/root/include/TLine.h /soft/root/include/TAttText.h
-gucode.o: /soft/root/include/TArrayC.h /soft/root/include/TArrayS.h
-gucode.o: /soft/root/include/TArrayD.h
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/pilot.h
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcbank.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gclink.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcjloc.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gconsp.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcmate.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gccuts.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gckine.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcmulo.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcphys.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gctrak.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcflag.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcnum.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcstak.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gctmed.inc
-GeantPatch.o: /hdb2/offline/pro/GEANT321/geant321/gcunit.inc sckine.inc
-galicef.o: /hdb2/offline/pro/GEANT321/geant321/gcbank.inc
-galicef.o: /hdb2/offline/pro/GEANT321/geant321/gclink.inc
galicef.o: /hdb2/offline/pro/GEANT321/geant321/gcunit.inc
galicef.o: /hdb2/offline/pro/GEANT321/geant321/gcmutr.inc
galicef.o: /hdb2/offline/pro/GEANT321/geant321/gcgobj.inc
# FORTRAN sources
-FSRCS = GeantPatch.F galicef.F
+FSRCS = galicef.F
# C++ sources
}
//_____________________________________________________________________________
-char* TGeant3::VolName(Int_t id) const
+const char* TGeant3::VolName(Int_t id) const
{
//
// Return the volume name given the volume identifier
Int_t CurrentVol(Text_t *name, Int_t ©) const;
Int_t CurrentVolOff(Int_t off, Text_t *name, Int_t ©) const;
Int_t VolId(Text_t *name) const;
- char* VolName(Int_t id) const;
+ const char* VolName(Int_t id) const;
void TrackPosition(Float_t *xyz) const;
void TrackMomentum(Float_t *xyz) const;
Int_t Nvolumes() const;
void TGeant3::TrackPosition(Float_t*) const {}
void TGeant3::TrackMomentum(Float_t*) const {}
Int_t TGeant3::VolId(Text_t*) const {return 0;}
-char* TGeant3::VolName(Int_t ) const {return 0;}
+const char* TGeant3::VolName(Int_t ) const {return 0;}
Float_t TGeant3::TrackCharge() const {return 0;}
Float_t TGeant3::TrackMass() const {return 0;}
Bool_t TGeant3::TrackInside() const {return 0;}
+++ /dev/null
- CHARACTER*4 CHTREE
- INTEGER MTRACK, MPRIMA
- COMMON / SCKINE / MTRACK, MPRIMA
- +, CHTREE(2)