]> git.uio.no Git - u/mrichter/AliRoot.git/blame - GEANT321/ghits/gschit.F
Remove AliTRDconst.h
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gschit.F
CommitLineData
fe4da5cc 1*
2* $Id$
3*
4* $Log$
5* Revision 1.1.1.1 1995/10/24 10:21:11 cernlib
6* Geant
7*
8*
9#include "geant321/pilot.h"
10*CMZ : 3.21/02 29/03/94 15.41.20 by S.Giani
11*-- Author :
12 SUBROUTINE GSCHIT(ISET,IDET,ITRA,NUMBV,HITS,NHSUM,IHIT)
13C.
14C. ******************************************************************
15C. * *
16C. * Store HITS values into detector IUDET of set IUSET *
17C. * *
18C. * NUMBV volume numbers *
19C. * HITS array of values for the elements of current hit *
20C. * ITRA track number associated to this hit *
21C. * IHIT output parameter containing the hit number *
22C. * If IHIT=0 hit has not been stored *
23C. * *
24C. * Same action as GSAHIT but in case the physical volume *
25C. * specified by NUMBV contains already some hit for the *
26C. * same track, then the routine will sum up the last NHSUM *
27C. * elements of the hit. *
28C. * In order to use that routine , no packing must be *
29C. * specified for these NHSUM last hits. *
30C. * If NHSUM.LE.0 then GSCHIT is the same as GSAHIT. *
31C. * *
32C. * ==>Called by : <USER>, GUSTEP *
33C. * Authors R.Brun, M.Maire ********* *
34C. * *
35C. ******************************************************************
36C.
37#include "geant321/gcbank.inc"
38#include "geant321/gcunit.inc"
39 COMMON/GCLOCA/NLOCAL(2),JS,JD,JDH,JH,JHD,LOCAL(15)
40 DIMENSION NUMBV(*),HITS(*)
41 PARAMETER (MAXINT=2147483647)
42 SAVE NMESS
43 DATA NMESS/0/
44C.
45C. ------------------------------------------------------------------
46C.
47 CALL GSAHIT(ISET,IDET,ITRA,NUMBV,HITS,IHIT)
48 IF(IHIT.LE.1)GO TO 999
49 IF(NHSUM.LE.0)GO TO 999
50C
51 NV=IQ(JD+1)
52 NH=IQ(JD+3)
53 NW=NV+NH+1
54 JNEWH = JHD+(IHIT-1)*NW
55 JCURR = JNEWH
56C
57 DO 30 I=1,IHIT-1
58 JCURR = JCURR-NW
59C
60C Check if track number is ITRA
61C
62 IF(ITRA.NE.IQ(JCURR+1))GO TO 999
63C
64C Check if volume numbers are the same
65C
66 DO 10 J=2,NV+1
67 IF(IQ(JCURR+J).NE.IQ(JNEWH+J))GO TO 30
68 10 CONTINUE
69C
70C Volumes are the same. Now sum the last NHSUM hits
71C
72 DO 20 K=NW,NW-NHSUM+1,-1
73 IF(IQ(JCURR+K).GT.MAXINT-IQ(JNEWH+K)) THEN
74 IQ(JCURR+K) = MAXINT
75 NMESS=NMESS+1
76 IF(NMESS.LT.10)THEN
77 WRITE(CHMAIL,10000)IQ(JSET+ISET),IQ(JS+IDET)
78 CALL GMAIL(0,0)
79 ENDIF
80 ELSE
81 IQ(JCURR+K)=IQ(JCURR+K)+IQ(JNEWH+K)
82 ENDIF
83 20 CONTINUE
84C
85C Remove temporarily stored hit
86C
87 IHIT=IHIT-1
88 IQ(JH+IDET)=IQ(JH+IDET)-NW
89 GO TO 999
90 30 CONTINUE
91C
9210000 FORMAT(' ***** GSCHIT OVERFLOW WHEN IUSET= ',A4,' IUDET= ',A4)
93 999 END