(file) Return to h_fpp_statistics.f CVS log (file) (dir) Up to [HallC] / Analyzer / HTRACKING

  1 frw   1.1.2.1       SUBROUTINE h_fpp_statistics(ABORT,err)
  2               *--------------------------------------------------------
  3               *    Hall C  HMS Focal Plane Polarimeter Code
  4               *
  5               *  Purpose: statistical studies of FPP portion of HMS event
  6               * 
  7               *  Created by Frank R. Wesselmann,  February 2004
  8               *
  9               *--------------------------------------------------------
 10               
 11                     IMPLICIT NONE
 12               
 13                     INCLUDE 'hms_data_structures.cmn'
 14                     INCLUDE 'hms_geometry.cmn'
 15                     INCLUDE 'hms_statistics.cmn'
 16 frw   1.1.2.2       include 'gen_detectorids.par'
 17 frw   1.1.2.1       include 'gen_decode_common.cmn'
 18                     INCLUDE 'hms_fpp_event.cmn'
 19                     INCLUDE 'hms_fpp_params.cmn'
 20 cdaq  1.1.2.4       include 'hms_id_histid.cmn'   
 21 frw   1.1.2.1 
 22                     character*16 here
 23                     parameter (here= 'h_fpp_statistics')
 24               
 25                     logical ABORT
 26                     character*(*) err
 27               
 28                     real*4 uTrack, uWire
 29                     real*4 mindist, rdist, rtime, residual, drift
 30 cdaq  1.1.2.4       real*4 DC_coords(3), FP_coords(3)
 31                     real*4 x,y,z,mx,my,bx,by,z0,u, wirepos
 32 frw   1.1.2.1 
 33                     integer*4 iPlane, iSet, iCham, iLay, iClust, iTrk, iHit, iRaw, iWire, ii
 34               
 35               
 36                     ABORT= .FALSE.
 37                     err= ' '
 38 cdaq  1.1.2.4 
 39               
 40               ** geometric alignment against HMS
 41               
 42                     if (.TRUE.) then
 43               
 44               *       * for each trigger, find the distance between each wire that fired
 45               *       * and the HMS track IN THAT WIRE'S PLANE'S COORDINATE
 46                       if (HNTRACKS_FP.ge.1) then
 47                         do iSet=1,H_FPP_N_DCSETS
 48                           do iCham=1,H_FPP_N_DCINSET
 49                            do iLay=1,H_FPP_N_DCLAYERS
 50                              if (HFPP_nClusters(iSet,iCham,iLay).gt.0) then
 51               
 52               *                * rotate to local coords, project HMS track to this plane
 53                                FP_coords(1) = hsx_fp	 ! transform offsets
 54                                FP_coords(2) = hsy_fp
 55                                FP_coords(3) = 0.0
 56 brash 1.1.2.6                  call h_fpp_FP2DC(iSet,iCham,iLay,.false.,FP_coords,DC_coords)
 57 cdaq  1.1.2.4                  bx = DC_coords(1)
 58                                by = DC_coords(2)
 59                                z0 = DC_coords(3)
 60               
 61                                FP_coords(1) = hsxp_fp	 ! transform slope
 62                                FP_coords(2) = hsyp_fp
 63                                FP_coords(3) = 1.0
 64 brash 1.1.2.6                  call h_fpp_FP2DC(iSet,iCham,iLay,.true.,FP_coords,DC_coords)
 65 cdaq  1.1.2.4                  mx = DC_coords(1)
 66                                my = DC_coords(2)
 67               
 68                                z = HFPP_layerZ(iSet,iCham,iLay)
 69                                x = bx + mx * (z-z0)
 70                                y = by + my * (z-z0)
 71               
 72               *                * determine generalized in-layer coordinate
 73                                u = HFPP_direction(iSet,iCham,iLay,1) * x
 74                    >             + HFPP_direction(iSet,iCham,iLay,2) * y
 75               
 76               *                 print *,' A ',x,y,z, ' z0 ',z0,'  s ',mx,my
 77               *                 print *,' B ',hsx_fp + hsxp_fp*(z+HFPP_Zoff(iSet)),
 78               *     >                         hsy_fp + hsyp_fp*(z+HFPP_Zoff(iSet)),
 79               *     >                         z+HFPP_Zoff(iSet),  '  s ',hsxp_fp,hsyp_fp
 80               
 81                                do iClust=1,HFPP_nClusters(iSet,iCham,iLay)
 82                                 do iHit=1,HFPP_nHitsinCluster(iSet,iCham,iLay,iClust)
 83               
 84                                   iRaw = HFPP_Clusters(iSet,iCham,iLay,iClust,iHit)
 85                                   iWire = HFPP_raw_wire(iRaw)
 86 cdaq  1.1.2.4 
 87                                   wirepos = HFPP_layeroffset(iSet,iCham,iLay)
 88                    >                      + HFPP_spacing(iSet,iCham,iLay)*iWire
 89               
 90 cdaq  1.1.2.5                     HFPP_dHMS(iSet,iCham,iLay,iClust,iHit) = u - wirepos
 91 cdaq  1.1.2.4 
 92                                 enddo !iHit
 93                                enddo !iClust
 94               
 95                              endif !HFPP_nClusters
 96                            enddo !iLay
 97                           enddo !iCham
 98                         enddo !iSet
 99                       endif !HNTRACKS_FP
100               
101               
102                     endif !hard-coded
103 frw   1.1.2.1 
104               
105               ** basic efficiency determinations
106               
107               *     * in each layer, find which wire a track went through
108                     do iSet=1,H_FPP_N_DCSETS
109                      if (HFPP_N_tracks(iSet).gt.0) then
110               
111                        do iTrk=1,HFPP_N_tracks(iSet)
112                         do iCham=1,H_FPP_N_DCINSET
113                          do iLay=1,H_FPP_N_DCLAYERS
114               
115                            call h_fpp_uTrack(iSet,iCham,iLay,iTrk,uTrack)
116               
117                            HFPP_stat_shouldhit(iSet,iCham,iLay,iTrk) =
118                    >            int(0.5 + (uTrack - HFPP_layeroffset(iSet,iCham,iLay))
119                    >                      / HFPP_spacing(iSet,iCham,iLay))
120               
121               *            * now lets see if ANY wire within acceptable range WAS hit
122               *            * and find the closest one, record the distance
123                            mindist = H_FPP_BAD_COORD
124 frw   1.1.2.1              HFPP_stat_diddhit(iSet,iCham,iLay,iTrk) = .false.
125                            if (HFPP_nClusters(iSet,iCham,iLay).gt.0) then
126                              do iClust=1,HFPP_nClusters(iSet,iCham,iLay)
127                               do iHit=1,HFPP_nHitsinCluster(iSet,iCham,iLay,iClust)
128               
129                                 iRaw = HFPP_Clusters(iSet,iCham,iLay,iClust,iHit)
130                                 iWire = HFPP_raw_wire(iRaw)
131               
132                                 rdist = uTrack - iWire * HFPP_spacing(iSet,iCham,iLay)
133                    >                           - HFPP_layeroffset(iSet,iCham,iLay)
134                                 if (abs(rdist).lt.abs(mindist)) then
135                                   mindist = rdist
136                                 endif
137               
138                                 if (abs(iWire-HFPP_stat_shouldhit(iSet,iCham,iLay,iTrk))
139                    >                   .le. HFPP_effic_dist) then
140                                   HFPP_stat_diddhit(iSet,iCham,iLay,iTrk) = .true.
141                                 endif
142               
143                               enddo !iHit
144                              enddo !iClust
145 frw   1.1.2.1              endif
146               
147                            HFPP_stat_dist2closest(iSet,iCham,iLay,iTrk) = mindist
148               
149               *            * convert to plane #s for CTP
150                            iPlane = H_FPP_N_DCLAYERS * H_FPP_N_DCINSET * (iSet-1)
151                    >       	    + H_FPP_N_DCLAYERS * (iCham-1)
152                    >       	    + iLay
153               
154               	     HFPP_stat_planeshould(iPlane,iTrk)
155                    >        = HFPP_stat_shouldhit(iSet,iCham,iLay,iTrk)
156               	     HFPP_stat_planedidd(iPlane,iTrk)
157                    >        = HFPP_stat_diddhit(iSet,iCham,iLay,iTrk)
158               
159                          enddo !iLay
160                         enddo !iCham
161                        enddo !iTrk
162               
163                      endif
164                     enddo !iSet
165               
166 frw   1.1.2.1 
167               *     * for external analysis, we need the wire number of hits, not the cluster
168               *     * reduce clusters to just one hit (wire) -- pick shortest drift time
169                     do iSet=1,H_FPP_N_DCSETS
170                      if (HFPP_N_tracks(iSet).ge.1) then
171                       do iTrk=1,HFPP_N_tracks(iSet)
172                        do iCham=1,H_FPP_N_DCINSET
173                         do iLay=1,H_FPP_N_DCLAYERS
174               
175                           iClust = HFPP_TrackCluster(iSet,iCham,iLay,iTrk)
176               	    ii = 0
177               	    residual = H_FPP_BAD_DRIFT
178               	    if (iClust.gt.0) then
179               
180                             rtime = H_FPP_BAD_TIME
181               	      if (HFPP_nHitsinCluster(iSet,iCham,iLay,iClust).gt.0) then
182               	       do iHit = 1,HFPP_nHitsinCluster(iSet,iCham,iLay,iClust)
183               	         iRaw = HFPP_Clusters(iSet,iCham,iLay,iClust,iHit)
184               	         if (HFPP_HitTime(iRaw).lt.rtime) then
185               	           ii = iRaw
186               		   rtime = HFPP_HitTime(iRaw)
187 frw   1.1.2.1 	         endif
188               	       enddo !iHit
189               	      endif
190               
191               *             * now also figure the residual of this hit
192                             iWire = HFPP_raw_wire(ii)
193                             uWire = HFPP_layeroffset(iSet,iCham,iLay)
194                    >              + HFPP_spacing(iSet,iCham,iLay)*iWire
195                             drift = HFPP_drift_dist(iSet,iCham,iLay,iWire)
196 puckett 1.1.2.7 
197                               if(drift.ne.h_fpp_bad_drift) then
198                 
199                                  call h_fpp_uTrack(iSet,iCham,iLay,iTrk,uTrack)
200                                  residual = uTrack - (uWire + drift)
201                 
202                               endif
203 frw     1.1.2.1 
204                 	    endif !iClust
205                 	    HFPP_TrackHit(iSet,iCham,iLay,iTrk) = ii
206                 	    HFPP_track_residual(iSet,iCham,iLay,iTrk) = residual
207                 
208                 	  enddo !iLay
209                          enddo !iCham
210                         enddo !iTrk
211                        endif
212                       enddo !iSet
213                 
214                 
215                       RETURN
216                       END

Analyzer/Replay: Mark Jones, Documents: Stephen Wood
Powered by
ViewCVS 0.9.2-cvsgraph-1.4.0