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

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