]> git.uio.no Git - u/mrichter/AliRoot.git/blob - GEANT321/ghits/gcdrif.F
Larger BOX in case CRT is present.
[u/mrichter/AliRoot.git] / GEANT321 / ghits / gcdrif.F
1 *
2 * $Id$
3 *
4 * $Log$
5 * Revision 1.1.1.1  1995/10/24 10:21:08  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  GCDRIF (RADD,ZMIN,ZMAX,DETREP,HITREP,IOUT)
13 C.
14 C.    **************************************************************************
15 C.    *                                                                        *
16 C.    *              Digitisation of Drift-  Chambers                          *
17 C.    *              --------------------------------                          *
18 C.    *                                                                        *
19 C.    *   Digitisation routine for a cylindrical drift chamber.                *
20 C.    * RADD      radius of cylinder in cm                                     *
21 C.    * ZMIN      z of lower end of cylinder                                   *
22 C.    * ZMAX      z of upper end of "                                          *
23 C.    * DETREP(1) number of wires                                              *
24 C.    * DETREP(2) wire spacing in PHI (radians)                                *
25 C.    * DETREP(3) cosine of wire angle                                         *
26 C.    * DETREP(4) sine of wire angle (signed like dphi/dz)                     *
27 C.    * DETREP(5) dphi/dz along wire                                           *
28 C.    * DETREP(6)  phi of point with z=0 on wire 1                             *
29 C.    * DETREP(7) drift velocity (cm/nsec)                                     *
30 C.    * DETREP(8) quantity describing the drift angle                          *
31 C.    *           if.ne.0 ==> user routine GUDTIM                              *
32 C.    * HITREP(1) phi coordinate of intersection                               *
33 C.    * HITREP(2) z coordinate                                                 *
34 C.    * HITREP(3) dphi/dr                                                      *
35 C.    * HITREP(4) dz/dr                                                        *
36 C.    * IOUT(1)   wire number (1..NWI with  increasing phi)  (-1 for           *
37 C.    *           bad DETREP parameters)                                       *
38 C.    * IOUT(2)   drift time (nsec) (+/- for phi(hit)>/< phi(wire)             *
39 C.    * IOUT(3)   digitised current division information (rel.  pos.           *
40 C.    *           along wire of charge) (per mille)                            *
41 C.    * IOUT(4)   amount of charge deposited to wire                           *
42 C.    * Coordinate systems along wire                                          *
43 C.    *     I.             Charge                   I.                         *
44 C.    *     .              |                        .                          *
45 C.    *     |              .                        |                          *
46 C.    *     =========================================  SENSE WIRE              *
47 C.    * ...................................................> Z (cm)            *
48 C.    *     Z              Z.                       Z.                         *
49 C.    *      L                                                                 *
50 C.    * ...............................................> X (arbitrary scale)   *
51 C.    *     0              X.                       L                          *
52 C.    *           X.                  (L-X.)                                   *
53 C.    * The scaling used is such that L . 1000.                                *
54 C.    * Knowing the position Z. of the deposit of charge,                      *
55 C.    *            Z.-ZL                                                       *
56 C.    *    X.                          =                           L           *
57 C.    * .          .....                                                       *
58 C.    *            Z.-ZL                                                       *
59 C.    * This information is stored into IOUT(3).                               *
60 C.    *   Routine to  calculate the  error on  the current  division           *
61 C.    * information as obtained by "GCDRIFT".                                  *
62 C.    * ICD       digitized     current     division     information           *
63 C.    *           (0 ... 1000)                                                 *
64 C.    * ERP       variance of Gaussian  distributed pedestral errors           *
65 C.    *           on the measured pulse heights  relative to the sum           *
66 C.    *           of the pulse heights                                         *
67 C.    * ERS       variance of  Gaussian distributed slope  errors on           *
68 C.    *           the measured  pulse heights  relative to  the each           *
69 C.    *           pulse heights                                                *
70 C.    *   Here we  assume that X.  has been determined  by measuring           *
71 C.    * the pulse heights I., I. with some statistical errors.                 *
72 C.    * X.   is then given by the formula                                      *
73 C.    *     X. = L . I./I.   with  I. . I.+I.                                  *
74 C.    * and its error is determined by                                         *
75 C.    *     .X. = -(X./I.) .I. + (L-X./I.) .I.                                 *
76 C.    * with the errors on measuring the pulse heights                         *
77 C.    *      .I. = .. + ...I.                                                  *
78 C.    *      .I. = .. + ...I.                                                  *
79 C.    * ..,  .. are of dimension  (I)  and represent the "pedestral"           *
80 C.    * errors;                                                                *
81 C.    * .., .. are the "slope" errors.                                         *
82 C.    * All  are   assumed  to  be  distributed   independently  (no           *
83 C.    * correlations), randomly and Gaussian around zero. This gives           *
84 C.    * the final result                                                       *
85 C.    *           ..      ..                  X.(L-X.)                         *
86 C.    *   .X. = - .. X. + .. (L-X.) + (..-..) ........                         *
87 C.    *           I.      I.                     L                             *
88 C.    *         ..................   .................                         *
89 C.    *               "pedestal"          "slope"                              *
90 C.    * In  GCDERR,  the X. derived from GCDRIF is set to                      *
91 C.    *      X. = X. + .X.    (but 0 . X. . L)                                 *
92 C.    * using  ERP .....  variance for ./I.  ,  ../I.  distributions           *
93 C.    *        ERS .....  variance for .., ..  distributions.                  *
94 C.    *                                                                        *
95 C.    *    ==>Called by : <USER>, GUDIGI                                       *
96 C.    *       Author    D.Mitaroff *********                                   *
97 C.    *                                                                        *
98 C.    **************************************************************************
99 C.
100       DIMENSION  DETREP(8), HITREP(4), IOUT(4)
101 #include "geant321/gconsp.inc"
102 C.
103 C.    -----------------------------------------------------------------
104 C.
105       ZREL    = 1000.
106       IOUT(1) = -1
107       NWI = DETREP(1)
108       WSP = DETREP(2)
109       DVL = DETREP(7)
110       IF (WSP .EQ. 0.)   GOTO 99
111       IF (DVL .EQ. 0.)   GOTO 99
112 C
113 C---- CALCULATE WIRE NUMBER.
114       FI = HITREP(1)
115       ZZ = HITREP(2)
116       FI0 = DETREP(6) + ZZ * DETREP(5)
117       DFI = FI - FI0
118    10 IF (DFI .GE. 0.)    GOTO 11
119       DFI = DFI + TWOPI
120       GOTO 10
121    11 IF (DFI .LT. TWOPI)   GOTO 12
122       DFI = DFI - TWOPI
123       GOTO 11
124    12 IW = DFI / WSP + 0.5
125       DIS = DFI - IW * WSP
126       IF (IW .EQ. NWI)   IW = 0
127       IOUT(1) = IW + 1
128 C
129 C---- CALCULATE DRIFT TIME.
130       DIS = DIS * RADD * DETREP(3)
131       IF ( DETREP(8) .NE. 0. )   GOTO 2
132       IOUT(2) = DIS / DVL
133       GOTO 3
134 C
135 C---- DRIFT TIME BY USER ROUTINE.
136     2 IOUT(2) = GUDTIM (DETREP,HITREP,IW+1,DIS)
137 C
138 C---- CALCULATE CURRENT DIVISION INFORMATION.
139     3 Z0 = ZZ + DIS * DETREP(4)
140       IF (Z0 .LT. ZMIN)   Z0 = ZMIN
141       IF (Z0 .GT. ZMAX)   Z0 = ZMAX
142       IOUT(3) = ZREL * (Z0 - ZMIN) / (ZMAX - ZMIN)
143       IOUT(4) = 0
144 C.
145   99  RETURN
146       END