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

  1 cdaq  1.1       subroutine s_one_ev_geometry
  2           *
  3           * This routine will get the detector position and size information from CTP,
  4           * then use this information for defining the different GEANT geometry structures
  5           *
  6           * August, 1994, Pat Welch, Oregon State University, tpw@physics.orst.edu
  7           *
  8           * Note: Subdivided volumes won't work for doing coordinate transforms.  Or
  9           *	at least I didn't see a method around them.  So I have defined all
 10           *	the subvolumes explicitly. (TPW)
 11           *
 12           * Modified from HMS version, h_one_ev_geometry, March 1995 by
 13           * Derek van Westrum (vanwestr@cebaf.gov)
 14           *
 15 cdaq  1.2 * $Log: s_one_ev_geometry.f,v $
 16 cdaq  1.3 * Revision 1.2  1995/10/06 18:24:18  cdaq
 17           * (DVW) Changed to ctp geometry variables and eliminated call to s_one_ev.par.
 18           *
 19 cdaq  1.2 * Revision 1.1  1995/07/31 15:23:38  cdaq
 20           * Initial revision
 21           * h_one_ev_geometry.f,v $
 22 cdaq  1.1 
 23                 implicit none
 24           
 25                 include 'sos_data_structures.cmn'
 26                 include 'sos_geometry.cmn'
 27                 include 'sos_calorimeter.cmn'
 28                 include 'sos_scin_parms.cmn'
 29           
 30 cdaq  1.2 *One day these will be ctp variables...
 31                 real*4    SHOWER_X_OFFSET,SHOWER_Y_OFFSET
 32                 parameter (SHOWER_X_OFFSET = 11.3)       ! offset
 33                 parameter (SHOWER_Y_OFFSET = 0.) ! offset
 34           
 35                 real*4    SHUT_WIDTH,SHUT_HEIGHT
 36                 parameter (SHUT_WIDTH = 100.)     ! full width of the det. hut
 37                 parameter (SHUT_HEIGHT = 800.)    ! full height of the det. hut
 38 cdaq  1.1       integer SHUTMEDIA                 ! non-sensitive tracking media
 39                 integer DETMEDIA                  ! sensitive tracking media
 40                 parameter (SHUTMEDIA = 1, DETMEDIA = 2)
 41                 real*4 hodoscale
 42 cdaq  1.3       parameter (hodoscale = 2.)
 43 cdaq  1.1       real*4 wcscale
 44           *      parameter (wcscale = 5.)
 45                 parameter (wcscale = 1.)
 46                 real*4 xwirelength                   
 47                 real*4 ywirelength                   
 48                 real*4 uwirelength
 49                 real*4 vwirelength
 50           
 51                 character*5 scinname 
 52                 character*5 layername
 53                 character*5 planename
 54                 character*5 plane
 55                 character*5 wire
 56                 character*5 blockname
 57                 integer isector
 58                 integer iplane
 59                 integer iwire
 60                 integer ichamber
 61                 integer ilayer
 62                 integer irow
 63           
 64 cdaq  1.1       integer ivolu			! internal volume number
 65                 real par(10)			! geometry parameters
 66                 real x, y, z			! offset position for placement of dets
 67                 integer i                         ! index variable
 68                 real*4 raddeg
 69                 parameter (raddeg = 3.14159265/180.)
 70           
 71           * First define two general media that everything is made of
 72           * one is insensitive, and the other is sensitive
 73           
 74                 call gstmed (SHUTMEDIA, 'air', 15, 0, 0,0.,20.,1.,0.5,1.,1.,0,0)
 75                 call gstmed (DETMEDIA, 'det', 15, 1, 0,0.,20.,1.,0.5,1.,1.,0,0)
 76           
 77           * Now define the mother volume that the detectors sit in
 78                 par(1) = SHUT_WIDTH / 2.          ! half width in x of mother volume
 79                 par(2) = SHUT_WIDTH / 2.          ! half width in y of mother volume
 80                 par(3) = SHUT_HEIGHT / 2.         ! half height in z of mother volume
 81                 call g_ugsvolu ('SHUT', 'BOX ', SHUTMEDIA, par, 3, ivolu)
 82                 call gsatt ('SHUT', 'SEEN', 0)	! can't see the hut
 83           
 84           * Define some wire lengths..
 85 cdaq  1.1 
 86                 xwirelength = 40.0
 87                 ywirelength = 60.0
 88                 uwirelength = xwirelength / SIN(sdc_alpha_angle(1))
 89                 vwirelength = xwirelength / SIN(sdc_alpha_angle(2))
 90           
 91           
 92           * Now define the wire chambers as a collection of planes
 93           * First the U and V planes.
 94           *
 95                 par(1) = ywirelength/2.
 96                 par(2) = xwirelength/2.
 97                 par(3) = wcscale * (sdc_zpos(2) - sdc_zpos(1))/ 2. ! half width of chamber planes
 98                 do ichamber = 1,2
 99                    do iplane = 1,2
100                      write(planename,'(a,a,a,a)') "W",char(64+ichamber),char(64+iplane),"U"
101                      call g_ugsvolu (planename, 'BOX ', DETMEDIA, par, 3, ivolu)
102                      write(planename,'(a,a,a,a)') "W",char(64+ichamber),char(64+iplane),"V"
103                      call g_ugsvolu (planename, 'BOX ', DETMEDIA, par, 3, ivolu)
104                    enddo
105                  enddo
106 cdaq  1.1 *
107           * Now do the X planes. 
108           *
109                 par(1) = ywirelength/2.
110                 par(2) = xwirelength/2.
111                 par(3) = wcscale * (sdc_zpos(2) - sdc_zpos(1))/ 2. ! half width of chamber planes
112                 do ichamber = 1,2
113                    do iplane = 1,2
114                      write(planename,'(a,a,a,a)') "W",char(64+ichamber),char(64+iplane),"X"
115                      call g_ugsvolu (planename, 'BOX ', DETMEDIA, par, 3, ivolu)
116                    enddo
117                  enddo
118           
119           ! make a volume for 6 planes.  The size here should be cool. DVW 18 jul 95
120                 par(1) = ywirelength/2.
121                 par(2) = xwirelength/2.
122                 par(3) = wcscale * (6./5. * (sdc_zpos(6) - sdc_zpos(1))) / 2.
123                 call g_ugsvolu ('WCHA', 'BOX ', DETMEDIA, par, 3, ivolu) ! Wire chamber
124                 call g_ugsvolu ('WCHB', 'BOX ', DETMEDIA, par, 3, ivolu) ! Wire chamber
125           
126           * Now place the planes within the wire chamber.  Start with U
127 cdaq  1.1       z = - wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
128                 call gspos ('WAAU', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! U plane
129                 z = - wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
130                 call gspos ('WABU', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! U plane
131                 z = - wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
132                 call gspos ('WBAU', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! U plane
133                 z = - wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
134                 call gspos ('WBBU', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! U plane
135           *
136                 z = - wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
137                 call gspos ('WAAX', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! X plane
138                 z =   wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
139                 call gspos ('WABX', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! X plane
140                 z = - wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
141                 call gspos ('WBAX', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! X plane
142                 z =   wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
143                 call gspos ('WBBX', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! X plane
144           *
145                 z =   wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
146                 call gspos ('WAAV', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! V plane
147                 z =   wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
148 cdaq  1.1       call gspos ('WABV', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! V plane
149                 z =   wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
150                 call gspos ('WBAV', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! V plane
151                 z =   wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
152                 call gspos ('WBBV', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! V plane
153           
154           * Now place the wire chambers in the mother volume
155           *
156                 x = sdc_xcenter(1)
157                 y = - sdc_ycenter(1)
158                 z = sdc_1_zpos
159                 call gspos ('WCHA', 1, 'SHUT', x, y, z, 0, 'ONLY') ! upper chamber
160                 x = sdc_xcenter(2)
161                 y = - sdc_ycenter(2)
162                 z = sdc_2_zpos
163                 call gspos ('WCHB', 1, 'SHUT', x, y, z, 0, 'ONLY') ! bottom chamber
164           *
165           * Define the individual wire cells
166           * See the file "displaynumbering.help" for a description of the numbering of the
167           * various detector elements
168           *
169 cdaq  1.1 *****
170           *UUUU
171           *****
172                 par(1) = sdc_pitch(1) / 2./1000.        ! make the cells "wire" thin
173                 par(2) = uwirelength/2.
174                 par(3) = (sdc_zpos(2) - sdc_zpos(1))/ 2./1000. ! half width of chamber planes
175           *
176           * First define all the "boxes" for all the U wires in both chambers...
177           *
178                 do ichamber=1,2
179                  do isector=1,4
180                     do iwire = 1,24
181                       write (wire,'(a,a,a,a)') char(64 + ichamber),'U',
182                $             char(64 + isector),char(64 + iwire)
183                       call g_ugsvolu (wire, 'BOX ', DETMEDIA, par, 3, ivolu) ! U cell
184                       call gsatt (wire, 'SEEN', 0) ! can't see the wire cells
185                     enddo
186                  enddo
187                 enddo
188           *
189                 par(1) = sdc_pitch(1) / SIN(sdc_alpha_angle(1))        
190 cdaq  1.1 *
191           * Now position the U wires plane by plane...
192                 do ichamber=1,2
193                    x = -(sdc_nrwire(1) + 1.) / 2. * par(1)
194                    do isector=1,2
195                       do iwire = 1,24
196                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'AU'
197                          write (wire,'(a,a,a,a)') char(64 + ichamber),'U',
198                $             char(64 + isector),char(64 + iwire)
199                          x = x + par(1)
200                          call gspos (wire, 1, plane, x, 0., 0., 3, 'ONLY')
201                       enddo
202                    enddo
203                    x = -(sdc_nrwire(1) + 1.) / 2. * par(1)
204                    do isector = 3,4
205                       do iwire = 1,24
206                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'BU'
207                          write (wire,'(a,a,a,a)') char(64 + ichamber),'U',
208                $              char(64 + isector),char(64 + iwire)
209                          x = x + par(1)
210                          call gspos (wire, 1, plane, x, 0., 0., 3, 'ONLY')
211 cdaq  1.1             enddo
212                    enddo
213                 enddo
214           *
215           *
216           * Now position the X wires plane by plane...
217           *****
218           *XXX
219           *****
220                 par(1) = sdc_pitch(3) / 2. /1000.       ! half width of cell
221                 par(2) = xwirelength/2.             ! the length of the xwirelengths
222                 par(3) = (sdc_zpos(4) - sdc_zpos(3))/ 2./1000. ! half width of chamber planes
223           *
224           * First define all the "boxes" for all the X wires in both chambers...
225           *
226                 do ichamber=1,2
227                  do isector=1,8
228                     do iwire = 1,16
229                       write (wire,'(a,a,a,a)') char(64 + ichamber),'X',
230                $             char(64 + isector),char(64 + iwire)
231                       call g_ugsvolu (wire, 'BOX ', DETMEDIA, par, 3, ivolu) ! X cell
232 cdaq  1.1             call gsatt (wire, 'SEEN', 0) ! can't see the wire cells
233                     enddo
234                  enddo
235                 enddo
236           *
237                 par(1) = sdc_pitch(3)
238           *
239           * Now position the X wires plane by plane...
240                 do ichamber=1,2
241                    x = -(sdc_nrwire(3) + 1.) / 2. * par(1) 
242                    do isector=1,4
243                       do iwire = 1,16
244                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'AX'
245                          write (wire,'(a,a,a,a)') char(64 + ichamber),'X',
246                $             char(64 + isector),char(64 + iwire)
247                          x = x + par(1)
248                          call gspos (wire, 1, plane, x, 0., 0., 0, 'ONLY')
249                       enddo
250                    enddo
251                    x = -(sdc_nrwire(3) + 1.) / 2. * par(1)
252                    do isector = 5,8
253 cdaq  1.1             do iwire = 1,16
254                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'BX'
255                          write (wire,'(a,a,a,a)') char(64 + ichamber),'X',
256                $              char(64 + isector),char(64 + iwire)
257                          x = x + par(1)
258                          call gspos (wire, 1, plane, x, 0., 0., 0, 'ONLY')
259                       enddo
260                    enddo
261                 enddo
262           *
263           *
264           *****
265           *VVVV
266           *****
267                 par(1) = sdc_pitch(5) / 2./1000.        ! half width of cell
268                 par(2) = vwirelength/2.
269                 par(3) = (sdc_zpos(6) - sdc_zpos(5))/ 2./1000. ! half width of chamber planes
270           *
271           * First define all the "boxes" for all the V wires in both chambers...
272           *
273                 do ichamber=1,2
274 cdaq  1.1        do isector=1,4
275                     do iwire = 1,24
276                       write (wire,'(a,a,a,a)') char(64 + ichamber),'V',
277                $             char(64 + isector),char(64 + iwire)
278                       call g_ugsvolu (wire, 'BOX ', DETMEDIA, par, 3, ivolu) ! V cell
279                       call gsatt (wire, 'SEEN', 0) ! can't see the wire cells
280                     enddo
281                  enddo
282                 enddo
283           *
284                 par(1) = sdc_pitch(5) / SIN(sdc_alpha_angle(5))        
285           
286           * Now position the V wires plane by plane...
287                 do ichamber=1,2
288                    x = -(sdc_nrwire(5) + 1.) / 2. * par(1)
289                    do isector=1,2
290                       do iwire = 1,24
291                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'AV'
292                          write (wire,'(a,a,a,a)') char(64 + ichamber),'V',
293                $             char(64 + isector),char(64 + iwire)
294                          x = x + par(1)
295 cdaq  1.1                call gspos (wire, 1, plane, x, 0., 0., 4, 'ONLY')
296                       enddo
297                    enddo
298                    x = -(sdc_nrwire(5) + 1.) / 2. * par(1)
299                    do isector = 3,4
300                       do iwire = 1,24
301                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'BV'
302                          write (wire,'(a,a,a,a)') char(64 + ichamber),'V',
303                $              char(64 + isector),char(64 + iwire)
304                          x = x + par(1)
305                          call gspos (wire, 1, plane, x, 0., 0., 4, 'ONLY')
306                       enddo
307                    enddo
308                 enddo
309           *
310           *
311           * Now define the hodoscope layers
312           * See the file "displaynumbering.help" for a description of the numbering of the
313           * various detector elements
314           
315 cdaq  1.2       par(1) = sscin_1x_size * sscin_1x_nr / 2.
316                 par(2) = sscin_1y_size * sscin_1y_nr / 2.
317                 par(3) = sscin_1x_dzpos * hodoscale / 2.
318 cdaq  1.1       call g_ugsvolu ('HDX1', 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
319                 call g_ugsvolu ('HDY1', 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
320 cdaq  1.2       call gsatt ('HDX1', 'SEEN', 0)   ! can't see the hodo box
321                 call gsatt ('HDY1', 'SEEN', 0)   ! can't see the hodo box
322                 par(1) = sscin_2x_size * sscin_2x_nr / 2.
323                 par(2) = sscin_2y_size * sscin_2y_nr / 2.
324                 par(3) = sscin_2x_dzpos * hodoscale /2.
325 cdaq  1.1       call g_ugsvolu ('HDX2', 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
326                 call g_ugsvolu ('HDY2', 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
327 cdaq  1.2       call gsatt ('HDX2', 'SEEN', 0)   ! can't see the hodo box
328                 call gsatt ('HDY2', 'SEEN', 0)   ! can't see the hodo box
329 cdaq  1.1 
330           ! box for front hodos
331 cdaq  1.2       par(1) = sscin_1x_size * sscin_1x_nr / 2.
332                 par(2) = sscin_1y_size * sscin_1y_nr / 2.
333                 par(3) = sscin_1x_dzpos*hodoscale + (sscin_1y_zpos-sscin_1x_zpos)/2.
334 cdaq  1.1       call g_ugsvolu ('HOD1', 'BOX ', DETMEDIA, par, 3, ivolu) ! hodoscope box
335                 call gsatt ('HOD1', 'SEEN', 0)	! can't see the hodo box
336           
337           ! box for back hodos
338 cdaq  1.2       par(1) = sscin_2x_size * sscin_2x_nr / 2.
339                 par(2) = sscin_2y_size * sscin_2y_nr / 2.
340                 par(3) = sscin_2x_dzpos*hodoscale + (sscin_2y_zpos-sscin_2x_zpos)/2.
341 cdaq  1.1       call g_ugsvolu ('HOD2', 'BOX ', DETMEDIA, par, 3, ivolu) ! hodoscope box
342                 call gsatt ('HOD2', 'SEEN', 0)	! can't see the hodo box
343           *                                         added by Derek
344           *
345 cdaq  1.2       x = sscin_1x_offset
346                 y = -sscin_1y_offset
347 cdaq  1.1       z = sscin_1x_zpos
348                 call gspos ('HOD1', 1, 'SHUT', x, y, z, 0, 'ONLY') ! lower hodo
349 cdaq  1.2       x = sscin_2x_offset
350                 y = -sscin_2y_offset
351 cdaq  1.1       z = sscin_2x_zpos
352                 call gspos ('HOD2', 1, 'SHUT', x, y, z, 0, 'ONLY') ! upper hodo
353           
354 cdaq  1.2       z= -(sscin_1x_offset*hodoscale + (sscin_1y_zpos-sscin_1x_zpos))/2.
355 cdaq  1.1       call gspos ('HDX1', 1, 'HOD1', 0., 0., z, 0, 'ONLY') ! X plane
356                 call gspos ('HDY1', 1, 'HOD1', 0., 0., -z, 0, 'ONLY') ! Y plane
357 cdaq  1.2       z= -(sscin_2x_offset*hodoscale + (sscin_2y_zpos-sscin_2x_zpos))/2.
358 cdaq  1.1       call gspos ('HDX2', 1, 'HOD2', 0., 0., z, 0, 'ONLY') ! X plane
359                 call gspos ('HDY2', 1, 'HOD2', 0., 0., -z, 0, 'ONLY') ! Y plane
360           
361           * Now define the strips for the hodoscopes
362           
363 cdaq  1.2       x = (sscin_1x_nr + 1.) * sscin_1x_size / 2. ! starting loci
364                 do i = 1, sscin_1x_nr
365 cdaq  1.1         x = x - sscin_1x_size
366                   write (scinname,'(a,a)') 'H1X',char(64 + i)
367                   par(1) = sscin_1x_size / 2. ! half width of X strips
368 cdaq  1.2         par(2) = sscin_1y_size * sscin_1y_nr / 2.
369                   par(3) = sscin_1x_dzpos * hodoscale / 2. !half thickness of hodoscope in z
370 cdaq  1.1         call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
371                   call gspos (scinname, i, 'HDX1', x, 0., 0., 0, 'ONLY')
372                 enddo
373 cdaq  1.2       y = (sscin_1y_nr + 1.) * sscin_1y_size / 2. ! starting loci
374                 do i = 1, sscin_1y_nr
375 cdaq  1.1         y = y - sscin_1y_size
376                   write (scinname,'(a,a)') 'H1Y',char(64 + i)
377 cdaq  1.2         par(1) = sscin_1x_size * sscin_1x_nr / 2.
378 cdaq  1.1                                         ! half width of hodoscope in x
379                   par(2) = sscin_1y_size / 2.	! half width of X strips
380 cdaq  1.2         par(3) = sscin_1y_dzpos * hodoscale / 2. !half thickness of hodoscope in z
381 cdaq  1.1         call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
382                   call gspos (scinname, i, 'HDY1', 0., y, 0., 0, 'ONLY')
383                 enddo
384 cdaq  1.2       x = (sscin_2x_nr + 1.) * sscin_2x_size / 2. ! starting loci
385                 do i = 1,sscin_2x_nr
386 cdaq  1.1         x = x - sscin_2x_size
387                   write (scinname,'(a,a)') 'H2X',char(64 + i)
388                   par(1) = sscin_2x_size / 2. ! half width of X strips
389 cdaq  1.2         par(2) = sscin_2y_size * sscin_2y_nr / 2.
390                   par(3) = sscin_2x_dzpos * hodoscale / 2. !half thickness of hodoscope in z
391 cdaq  1.1         call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
392                   call gspos (scinname, i, 'HDX2', x, 0., 0., 0, 'ONLY')
393                 enddo
394 cdaq  1.2       y = (sscin_2y_nr + 1.) * sscin_2y_size / 2. ! starting loci
395                 do i = 1, sscin_2y_nr
396 cdaq  1.1         y = y - sscin_2y_size
397                   write (scinname,'(a,a)') 'H2Y',char(64 + i)
398 cdaq  1.2         par(1) = sscin_2x_size * sscin_2x_nr / 2.
399 cdaq  1.1         par(2) = sscin_2y_size / 2.	! half width of X strips
400 cdaq  1.2         par(3) = sscin_2y_dzpos * hodoscale / 2. !half thickness of hodoscope in z
401 cdaq  1.1         call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
402                   call gspos (scinname, i, 'HDY2', 0., y, 0., 0, 'ONLY')
403                 enddo
404           
405           * Now define the shower detector
406           * See the file "displaynumbering.help" for a description of the numbering of the
407           * various detector elements
408           
409           ! half width of the shower in x
410                 par(1) = smax_cal_rows * scal_block_zsize / 2.
411           ! half width of the shower in y
412                 par(2) = scal_block_ysize / 2.
413           ! half height of the shower detector
414                 par(3) = smax_cal_columns * scal_block_xsize / 2.
415                 call g_ugsvolu ('SHOW', 'BOX ', DETMEDIA, par, 3, ivolu)
416                 x = SHOWER_X_OFFSET 
417                 y = SHOWER_Y_OFFSET
418                 z = scal_1pr_zpos + smax_cal_columns*scal_block_xsize/2.
419                 call gspos ('SHOW', 1, 'SHUT', x, y, z, 0, 'ONLY')
420                 call gsatt ('SHOW','SEEN',0)
421           
422 cdaq  1.1 ! half width of the shower in x
423                 par(1) = smax_cal_rows * scal_block_zsize / 2.
424           ! half width of the shower in y
425                 par(2) = scal_block_ysize / 2.
426           ! half height of the shower detector
427                 par(3) = scal_block_xsize / 2.
428                 call g_ugsvolu ('LAY1', 'BOX ', DETMEDIA, par, 3, ivolu)
429                 call g_ugsvolu ('LAY2', 'BOX ', DETMEDIA, par, 3, ivolu)
430                 call g_ugsvolu ('LAY3', 'BOX ', DETMEDIA, par, 3, ivolu)
431                 call g_ugsvolu ('LAY4', 'BOX ', DETMEDIA, par, 3, ivolu)
432           
433                 z = -(smax_cal_columns + 1.) / 2. * scal_block_xsize
434                 z = z + scal_block_xsize
435                 call gspos('LAY1', 1, 'SHOW', 0., 0., z, 0, 'ONLY')
436                 z = z + scal_block_xsize
437                 call gspos('LAY2', 1, 'SHOW', 0., 0., z, 0, 'ONLY')
438                 z = z + scal_block_xsize
439                 call gspos('LAY3', 1, 'SHOW', 0., 0., z, 0, 'ONLY')
440                 z = z + scal_block_xsize
441                 call gspos('LAY4', 1, 'SHOW', 0., 0., z, 0, 'ONLY')
442           
443 cdaq  1.1       par(1) = scal_block_zsize / 2.	! half width of a block
444                 par(2) = scal_block_ysize / 2.	! half length of a block
445                 par(3) = scal_block_xsize / 2.	! half height of a block
446 cdaq  1.2       do ilayer =1,smax_cal_columns
447                    do irow = 1,smax_cal_rows
448 cdaq  1.1             write (blockname,'(a,i1,a)') 'BL',ilayer,char(64 + irow)
449                       call g_ugsvolu (blockname, 'BOX ', DETMEDIA, par, 3, ivolu)
450                    enddo
451                 enddo
452           *
453 cdaq  1.2       do ilayer =1,smax_cal_columns
454 cdaq  1.1          x =  (smax_cal_rows - 1.) / 2. * scal_block_zsize
455 cdaq  1.2          do irow = 1,smax_cal_rows
456 cdaq  1.1             write (blockname,'(a,i1,a)') 'BL',ilayer,char(64 + irow)
457                       write (layername,'(a,i1)') 'LAY',ilayer
458                       call gspos(blockname, 1, layername, x, 0., 0., 0, 'ONLY')
459                       x = x - scal_block_zsize
460                    enddo
461                 enddo
462           
463           *
464           
465                 end

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