(file) Return to structures.inc CVS log (file) (dir) Up to [HallC] / simc_gfortran

  1 gaskelld 1.1 ! STRUCTURES.INC 
  2              !   (note that all initializations of fields have been moved
  3              !    into the file "structures_init.inc")
  4              
  5              ! Define some BASIC record structures and associated parameters
  6              
  7              ! ... generic cut -->  initialized with MAX large and MIN small
  8              	type cutstype
  9                              sequence
 10              		real*8		min, max
 11              	end type
 12              
 13              ! ... generic range (rather than a cut) --> initialized with HI small and LO large
 14              	type rangetype
 15                              sequence
 16              		real*8		lo, hi
 17              	end type
 18              
 19              ! ... generic Cartesian vector
 20              	integer*4 nCartesianfields
 21              	parameter (nCartesianfields = 3)
 22 gaskelld 1.1 	type Cartesian
 23                              sequence
 24              		real*8		x,y,z
 25              	end type
 26              
 27              ! ... minimal description of scattered particles, or cuts/ranges on these qties
 28              
 29              ! declare structures arm and arm2 first
 30                      type arm
 31                              sequence
 32              		real*8		delta, yptar, xptar, z
 33              	end type 		
 34              
 35                      type arm2
 36                              sequence
 37              		real*8		delta, yptar, xptar, z
 38              	end type 		
 39              
 40              
 41              	type double_arm
 42                              sequence
 43 gaskelld 1.1 		type(arm)::e
 44              		type(arm2)::p
 45              	end type
 46              
 47              	type arm_cuts
 48                           sequence
 49              	     type(cutstype):: delta, yptar, xptar, z
 50              	end type
 51              
 52              	type arm_cuts2
 53                           sequence
 54              	     type(cutstype):: delta, yptar, xptar, z
 55              	end type
 56              
 57              	type double_arm_cuts
 58                              sequence
 59              		type(arm_cuts)::e
 60              		type (arm_cuts2)::p
 61              	end type
 62              
 63              	type arm_range
 64 gaskelld 1.1              sequence
 65              	     type(rangetype):: delta,xptar,yptar,z
 66                      end type
 67              
 68              	type arm_range2
 69                           sequence
 70              	     type(rangetype):: delta,xptar,yptar,z
 71                      end type
 72              
 73              	type double_arm_range
 74                              sequence
 75              		type(arm_range)::e
 76              		type(arm_range2)::p
 77              	end type
 78              
 79              ! ... generic focal plane vectors (transport convention, in both spectrometers)
 80              
 81                     type arm_FP
 82                         sequence
 83                         real*8		x, dx, y, dy, path
 84                     end type
 85 gaskelld 1.1 
 86                     type arm_FP2
 87                         sequence
 88                         real*8		x, dx, y, dy, path
 89                     end type
 90              
 91              	type double_arm_FP
 92                              sequence
 93              		type(arm_FP)::e
 94              		type(arm_FP2)::p
 95              	end type
 96              
 97              ! ... full description of a given particle
 98              	integer*4 narm_fullfields
 99              	parameter (narm_fullfields = 8)
100              	type arm_full
101                              sequence
102              		real*8	delta,xptar,yptar,z
103              		real*8	theta,phi,E,P
104              	end type
105              
106 gaskelld 1.1 	type cuts_true
107                              sequence
108              		type(cutstype)::	Em, Pm
109              	end type
110              
111              ! EVENT structures
112              
113              ! ... description of event -- both actual and reconstructed (measured) versions calculated
114              
115              ! NEVENTFIELDS is used to copy from one /event/ record into another.
116              ! IF YOU MODIFY THIS STRUCTURE, YOU MUST MAKE SURETHAT NEVENTFIELDS
117              ! IS UPDATED ACCORDINGLY, OR BAD THINGS CAN HAPPEN.
118              
119              	integer*4 neventfields
120              	parameter (neventfields = 28 + 2*narm_fullfields + 3*nCartesianfields)
121              	type event
122                              sequence
123              		real*8	Ein
124              		real*8	Em, Pm
125              		real*8	Emiss, Pmiss
126              		real*8	Pmx, Pmy, Pmz
127 gaskelld 1.1 		real*8	PmPar, PmPer, PmOop
128              		real*8	nu, q, Q2, Trec, W, Mrec
129              		real*8	epsilon, theta_pq, theta_tarq,phi_pq,phi_targ
130              		real*8  beta, phi_s, phi_c
131              		real*8  zhad,pt2,xbj
132              		type (arm_full):: e, p
133              		type (Cartesian):: ue, up, uq
134              	end type
135              
136              ! ... target-specific event quantities
137              	type event_target
138                              sequence
139              		real*8	x, y, z, rasterx, rastery
140              		real*8	teff(3), Eloss(3), Coulomb
141              	end type
142              
143              ! ... quantities that are determined only once per event
144              	type event_main
145                              sequence
146              		real*8 weight, SF_weight, gen_weight, jacobian
147              		real*8 Ein_shift, Ee_shift
148 gaskelld 1.1 		real*8 sigcc, sigcc_recon, sigcent
149                              real*8 epsilon,theta_pq,theta_tarq,phi_pq,phi_targ,beta
150              		real*8 w,t,tmin,q2
151                              real*8 pcm,thetacm,phicm,wcm
152              		real*8 davejac,johnjac
153              		type(event_target)::target
154              		type(double_arm):: SP, RECON
155              		type(double_arm_FP)::FP
156              		real*8 Trec
157              	end type
158              
159              ! ... a gross structure that serves merely to catch all interesting qties for a 'central' event
160                      type event_central_rad
161                              sequence
162              		real*8 hardcorfac, etatzai, frac(3), lambda(3), bt(2)
163              		real*8 c_int(0:3), c_ext(0:3), c(0:3), g_int, g_ext, g(0:3)
164                      end type
165              
166              	type event_central
167                              sequence
168              		real*8		sigcc, nu, q, Q2
169 gaskelld 1.1 		real*8		Em, Pm, W, MM
170              		type(event_central_rad)::rad
171              		type (arm_full):: e, p
172              	end type
173              
174              ! OTHER stuff
175              
176              ! ... spectrometer settings and specifications
177                    type spec_offset
178                            sequence
179              	      real*8	x,y,z,xptar,yptar
180                    end type
181              
182                    type spec_offset2
183                            sequence
184              	      real*8	x,y,z,xptar,yptar
185                    end type
186              
187                     type spectrometer
188                         sequence
189                         real*8	P,theta,cos_th,sin_th,phi
190 gaskelld 1.1 	   type(spec_offset)::offset
191                     end type
192              
193                     type spectrometer2
194                         sequence
195                         real*8	P,theta,cos_th,sin_th,phi
196              	   type(spec_offset2)::offset
197                     end type
198              
199              
200              	type both_spec
201                              sequence
202              		type(spectrometer)::e
203              		type(spectrometer2)::p
204              	end type
205              
206              ! ... acceptance edges for TRUE and VERTEX quantities, both BEFORE reconstruction
207                      type edge_arm
208                         sequence
209              	   type(cutstype)::		E, yptar, xptar
210                      end type
211 gaskelld 1.1 
212                      type edge_arm2
213                         sequence
214              	   type(cutstype)::		E, yptar, xptar
215                      end type
216              
217              	type edge_true
218                              sequence
219              		type(edge_arm)::e
220              		type(edge_arm2)::p
221              		type (cutstype)::		Em, Pm, Mrec, Trec, Trec_struck
222              	end type
223              
224              ! ... pieces of the EXP dbase field that we'll need
225              	type EXP_field
226                              sequence
227              		real*8	charge
228              	end type
229              
230              ! ... generic description of a histogram axis
231              	type axis
232 gaskelld 1.1                 sequence
233              		real*8		min,max,bin
234              		integer		n
235              	end type
236              
237              ! ... ranges for the quantities that are generated randomly for each event / edges on quantities at the GENERATE stage
238                     type arm_limits
239                        sequence
240                        type (cutstype)::	delta, yptar, xptar, E
241                     end type
242              
243                     type arm_limits2
244                        sequence
245                        type (cutstype)::	delta, yptar, xptar, E
246                     end type
247              
248              	type gen_limits
249                              sequence
250              		type(arm_limits)::e
251              		type(arm_limits2)::p
252              		type (cutstype)::	sumEgen, Trec
253 gaskelld 1.1 		real*8		xwid, ywid
254              	end type
255              
256              ! ... ranges of event qties which actually contributed
257                      type contrib_gen
258                                sequence
259              		  type (arm_range):: e, p
260              		  type (rangetype):: Trec, sumEgen
261                      end type
262              
263              	type contrib_arm
264                              sequence
265                        	type (rangetype):: E, yptar, xptar
266                      end type
267              
268              
269              	type contrib_arm2
270                              sequence
271                        	type (rangetype):: E, yptar, xptar
272                      end type
273              
274 gaskelld 1.1         type contrib_true
275                                sequence
276              		  type(contrib_arm)::e
277              		  type(contrib_arm2)::p
278              		  type (rangetype):: Em, Pm, Trec
279                      end type
280              
281              	type contrib_vertex
282                          sequence
283                          type (rangetype):: Trec, Em, Pm
284                      end type
285              
286              	type contrib_rad
287                           sequence
288                           type (rangetype):: Egamma(3), Egamma_total
289                      end type
290              
291              	type contribtype
292                              sequence
293              		type(contrib_gen)::gen
294              		type(contrib_true)::tru
295 gaskelld 1.1 		type(double_arm_range)::SP
296              		type(contrib_vertex)::vertex
297              		type(contrib_rad)::rad
298              	end type
299              
300              ! ... values, and ranges of values which actually contributed, for useful slops (some are local to limits_init)
301              	type slop_item
302                              sequence
303              		real*8		lo, hi, used
304              	end type
305              	
306              	type slop_total
307                         sequence
308                         type (slop_item)::	Em, Pm
309                      end type
310              
311              	type slop_MC_arm
312                           sequence	
313                           type (slop_item):: delta, yptar, xptar
314                      end type
315              
316 gaskelld 1.1 	type slop_MC_arm2
317                           sequence
318                           type (slop_item):: delta, yptar, xptar
319                      end type
320              
321              	type slop_MC
322                               sequence
323                               type(slop_MC_arm)::e
324              		 type(slop_MC_arm2)::p
325                      end type
326              
327              	type sloptype
328                              sequence
329              		type(slop_total)::total
330              		type(slop_MC)::MC
331              	end type
332              
333              
334              ! ... sum and sum**2 of reconstruction errors (needed to get resolutions)
335                     type sums_electron
336                         sequence
337 gaskelld 1.1            real*8 delta,xptar,yptar,ytar
338                     end type
339              
340                     type sums_proton
341                         sequence
342                         real*8 delta,xptar,yptar,ytar
343                     end type
344              
345              	type sums_twoarm
346                              sequence
347              		type(sums_electron)::e
348              		type(sums_proton)::p
349              	end type

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