(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           * $Log:$ h_one_ev_geometry.f,v $
 16           
 17                 implicit none
 18           
 19                 include 'sos_data_structures.cmn'
 20                 include 'sos_geometry.cmn'
 21                 include 'sos_calorimeter.cmn'
 22 cdaq  1.1       include 'sos_scin_parms.cmn'
 23                 include 'sos_one_ev.par'
 24           
 25                 integer SHUTMEDIA                 ! non-sensitive tracking media
 26                 integer DETMEDIA                  ! sensitive tracking media
 27                 parameter (SHUTMEDIA = 1, DETMEDIA = 2)
 28                 real*4 hodoscale
 29                 parameter (hodoscale = 3.)
 30                 real*4 wcscale
 31           *      parameter (wcscale = 5.)
 32                 parameter (wcscale = 1.)
 33                 real*4 xwirelength                   
 34                 real*4 ywirelength                   
 35                 real*4 uwirelength
 36                 real*4 vwirelength
 37           
 38                 character*5 scinname 
 39                 character*5 layername
 40                 character*5 planename
 41                 character*5 wirename
 42                 character*5 chamber
 43 cdaq  1.1       character*5 plane
 44                 character*5 wire
 45                 character*5 blockname
 46                 integer isector
 47                 integer iplane
 48                 integer iwire
 49                 integer ichamber
 50                 integer ilayer
 51                 integer irow
 52           
 53                 integer ivolu			! internal volume number
 54                 real par(10)			! geometry parameters
 55                 real x, y, z			! offset position for placement of dets
 56                 integer i                         ! index variable
 57                 real*4 raddeg
 58                 parameter (raddeg = 3.14159265/180.)
 59           
 60           * First define two general media that everything is made of
 61           * one is insensitive, and the other is sensitive
 62           
 63                 call gstmed (SHUTMEDIA, 'air', 15, 0, 0,0.,20.,1.,0.5,1.,1.,0,0)
 64 cdaq  1.1       call gstmed (DETMEDIA, 'det', 15, 1, 0,0.,20.,1.,0.5,1.,1.,0,0)
 65           
 66           * Now define the mother volume that the detectors sit in
 67                 par(1) = SHUT_WIDTH / 2.          ! half width in x of mother volume
 68                 par(2) = SHUT_WIDTH / 2.          ! half width in y of mother volume
 69                 par(3) = SHUT_HEIGHT / 2.         ! half height in z of mother volume
 70                 call g_ugsvolu ('SHUT', 'BOX ', SHUTMEDIA, par, 3, ivolu)
 71                 call gsatt ('SHUT', 'SEEN', 0)	! can't see the hut
 72           
 73           * Define some wire lengths..
 74           
 75                 xwirelength = 40.0
 76                 ywirelength = 60.0
 77                 uwirelength = xwirelength / SIN(sdc_alpha_angle(1))
 78                 vwirelength = xwirelength / SIN(sdc_alpha_angle(2))
 79           
 80           
 81           * Now define the wire chambers as a collection of planes
 82           * First the U and V planes.
 83           *
 84                 par(1) = ywirelength/2.
 85 cdaq  1.1       par(2) = xwirelength/2.
 86                 par(3) = wcscale * (sdc_zpos(2) - sdc_zpos(1))/ 2. ! half width of chamber planes
 87                 do ichamber = 1,2
 88                    do iplane = 1,2
 89                      write(planename,'(a,a,a,a)') "W",char(64+ichamber),char(64+iplane),"U"
 90                      call g_ugsvolu (planename, 'BOX ', DETMEDIA, par, 3, ivolu)
 91                      write(planename,'(a,a,a,a)') "W",char(64+ichamber),char(64+iplane),"V"
 92                      call g_ugsvolu (planename, 'BOX ', DETMEDIA, par, 3, ivolu)
 93                    enddo
 94                  enddo
 95           *
 96           * Now do the X planes. 
 97           *
 98                 par(1) = ywirelength/2.
 99                 par(2) = xwirelength/2.
100                 par(3) = wcscale * (sdc_zpos(2) - sdc_zpos(1))/ 2. ! half width of chamber planes
101                 do ichamber = 1,2
102                    do iplane = 1,2
103                      write(planename,'(a,a,a,a)') "W",char(64+ichamber),char(64+iplane),"X"
104                      call g_ugsvolu (planename, 'BOX ', DETMEDIA, par, 3, ivolu)
105                    enddo
106 cdaq  1.1        enddo
107           
108           ! make a volume for 6 planes.  The size here should be cool. DVW 18 jul 95
109                 par(1) = ywirelength/2.
110                 par(2) = xwirelength/2.
111                 par(3) = wcscale * (6./5. * (sdc_zpos(6) - sdc_zpos(1))) / 2.
112                 call g_ugsvolu ('WCHA', 'BOX ', DETMEDIA, par, 3, ivolu) ! Wire chamber
113                 call g_ugsvolu ('WCHB', 'BOX ', DETMEDIA, par, 3, ivolu) ! Wire chamber
114           
115           * Now place the planes within the wire chamber.  Start with U
116                 z = - wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
117                 call gspos ('WAAU', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! U plane
118                 z = - wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
119                 call gspos ('WABU', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! U plane
120                 z = - wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
121                 call gspos ('WBAU', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! U plane
122                 z = - wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
123                 call gspos ('WBBU', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! U plane
124           *
125                 z = - wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
126                 call gspos ('WAAX', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! X plane
127 cdaq  1.1       z =   wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
128                 call gspos ('WABX', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! X plane
129                 z = - wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
130                 call gspos ('WBAX', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! X plane
131                 z =   wcscale * (1. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
132                 call gspos ('WBBX', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! X plane
133           *
134                 z =   wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
135                 call gspos ('WAAV', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! V plane
136                 z =   wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
137                 call gspos ('WABV', 1, 'WCHA', 0., 0., z, 0, 'ONLY') ! V plane
138                 z =   wcscale * (3. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
139                 call gspos ('WBAV', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! V plane
140                 z =   wcscale * (5. / 2.) * (sdc_zpos(2) -sdc_zpos(1))
141                 call gspos ('WBBV', 1, 'WCHB', 0., 0., z, 0, 'ONLY') ! V plane
142           
143           * Now place the wire chambers in the mother volume
144           *
145                 x = sdc_xcenter(1)
146                 y = - sdc_ycenter(1)
147                 z = sdc_1_zpos
148 cdaq  1.1       call gspos ('WCHA', 1, 'SHUT', x, y, z, 0, 'ONLY') ! upper chamber
149                 x = sdc_xcenter(2)
150                 y = - sdc_ycenter(2)
151                 z = sdc_2_zpos
152                 call gspos ('WCHB', 1, 'SHUT', x, y, z, 0, 'ONLY') ! bottom chamber
153           *
154           * Define the individual wire cells
155           * See the file "displaynumbering.help" for a description of the numbering of the
156           * various detector elements
157           *
158           *****
159           *UUUU
160           *****
161                 par(1) = sdc_pitch(1) / 2./1000.        ! make the cells "wire" thin
162                 par(2) = uwirelength/2.
163                 par(3) = (sdc_zpos(2) - sdc_zpos(1))/ 2./1000. ! half width of chamber planes
164           *
165           * First define all the "boxes" for all the U wires in both chambers...
166           *
167                 do ichamber=1,2
168                  do isector=1,4
169 cdaq  1.1           do iwire = 1,24
170                       write (wire,'(a,a,a,a)') char(64 + ichamber),'U',
171                $             char(64 + isector),char(64 + iwire)
172                       call g_ugsvolu (wire, 'BOX ', DETMEDIA, par, 3, ivolu) ! U cell
173                       call gsatt (wire, 'SEEN', 0) ! can't see the wire cells
174                     enddo
175                  enddo
176                 enddo
177           *
178                 par(1) = sdc_pitch(1) / SIN(sdc_alpha_angle(1))        
179           *
180           * Now position the U wires plane by plane...
181                 do ichamber=1,2
182                    x = -(sdc_nrwire(1) + 1.) / 2. * par(1)
183                    do isector=1,2
184                       do iwire = 1,24
185                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'AU'
186                          write (wire,'(a,a,a,a)') char(64 + ichamber),'U',
187                $             char(64 + isector),char(64 + iwire)
188                          x = x + par(1)
189                          call gspos (wire, 1, plane, x, 0., 0., 3, 'ONLY')
190 cdaq  1.1             enddo
191                    enddo
192                    x = -(sdc_nrwire(1) + 1.) / 2. * par(1)
193                    do isector = 3,4
194                       do iwire = 1,24
195                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'BU'
196                          write (wire,'(a,a,a,a)') char(64 + ichamber),'U',
197                $              char(64 + isector),char(64 + iwire)
198                          x = x + par(1)
199                          call gspos (wire, 1, plane, x, 0., 0., 3, 'ONLY')
200                       enddo
201                    enddo
202                 enddo
203           *
204           *
205           * Now position the X wires plane by plane...
206           *****
207           *XXX
208           *****
209                 par(1) = sdc_pitch(3) / 2. /1000.       ! half width of cell
210                 par(2) = xwirelength/2.             ! the length of the xwirelengths
211 cdaq  1.1       par(3) = (sdc_zpos(4) - sdc_zpos(3))/ 2./1000. ! half width of chamber planes
212           *
213           * First define all the "boxes" for all the X wires in both chambers...
214           *
215                 do ichamber=1,2
216                  do isector=1,8
217                     do iwire = 1,16
218                       write (wire,'(a,a,a,a)') char(64 + ichamber),'X',
219                $             char(64 + isector),char(64 + iwire)
220                       call g_ugsvolu (wire, 'BOX ', DETMEDIA, par, 3, ivolu) ! X cell
221                       call gsatt (wire, 'SEEN', 0) ! can't see the wire cells
222                     enddo
223                  enddo
224                 enddo
225           *
226                 par(1) = sdc_pitch(3)
227           *
228           * Now position the X wires plane by plane...
229                 do ichamber=1,2
230                    x = -(sdc_nrwire(3) + 1.) / 2. * par(1) 
231                    do isector=1,4
232 cdaq  1.1             do iwire = 1,16
233                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'AX'
234                          write (wire,'(a,a,a,a)') char(64 + ichamber),'X',
235                $             char(64 + isector),char(64 + iwire)
236                          x = x + par(1)
237                          call gspos (wire, 1, plane, x, 0., 0., 0, 'ONLY')
238                       enddo
239                    enddo
240                    x = -(sdc_nrwire(3) + 1.) / 2. * par(1)
241                    do isector = 5,8
242                       do iwire = 1,16
243                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'BX'
244                          write (wire,'(a,a,a,a)') char(64 + ichamber),'X',
245                $              char(64 + isector),char(64 + iwire)
246                          x = x + par(1)
247                          call gspos (wire, 1, plane, x, 0., 0., 0, 'ONLY')
248                       enddo
249                    enddo
250                 enddo
251           *
252           *
253 cdaq  1.1 *****
254           *VVVV
255           *****
256                 par(1) = sdc_pitch(5) / 2./1000.        ! half width of cell
257                 par(2) = vwirelength/2.
258                 par(3) = (sdc_zpos(6) - sdc_zpos(5))/ 2./1000. ! half width of chamber planes
259           *
260           * First define all the "boxes" for all the V wires in both chambers...
261           *
262                 do ichamber=1,2
263                  do isector=1,4
264                     do iwire = 1,24
265                       write (wire,'(a,a,a,a)') char(64 + ichamber),'V',
266                $             char(64 + isector),char(64 + iwire)
267                       call g_ugsvolu (wire, 'BOX ', DETMEDIA, par, 3, ivolu) ! V cell
268                       call gsatt (wire, 'SEEN', 0) ! can't see the wire cells
269                     enddo
270                  enddo
271                 enddo
272           *
273                 par(1) = sdc_pitch(5) / SIN(sdc_alpha_angle(5))        
274 cdaq  1.1 
275           * Now position the V wires plane by plane...
276                 do ichamber=1,2
277                    x = -(sdc_nrwire(5) + 1.) / 2. * par(1)
278                    do isector=1,2
279                       do iwire = 1,24
280                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'AV'
281                          write (wire,'(a,a,a,a)') char(64 + ichamber),'V',
282                $             char(64 + isector),char(64 + iwire)
283                          x = x + par(1)
284                          call gspos (wire, 1, plane, x, 0., 0., 4, 'ONLY')
285                       enddo
286                    enddo
287                    x = -(sdc_nrwire(5) + 1.) / 2. * par(1)
288                    do isector = 3,4
289                       do iwire = 1,24
290                          write (plane,'(a,a,a,a)') 'W',char(64 + ichamber),'BV'
291                          write (wire,'(a,a,a,a)') char(64 + ichamber),'V',
292                $              char(64 + isector),char(64 + iwire)
293                          x = x + par(1)
294                          call gspos (wire, 1, plane, x, 0., 0., 4, 'ONLY')
295 cdaq  1.1             enddo
296                    enddo
297                 enddo
298           *
299           *
300           * Now define the hodoscope layers
301           * See the file "displaynumbering.help" for a description of the numbering of the
302           * various detector elements
303           
304           ! half width of hodoscope in x
305                 par(1) = sscin_1x_size * LOWER_HODO_X_PADDLES / 2.
306           ! half width of hodoscope in y
307                 par(2) = sscin_1y_size * LOWER_HODO_Y_PADDLES / 2.
308           ! half thickness of hodoscope in z, times 2 because of stagger
309                 par(3) = HODO_THICKNESS * hodoscale
310                 call g_ugsvolu ('HDX1', 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
311                 call g_ugsvolu ('HDY1', 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
312           
313           ! half width of hodoscope in x
314                 par(1) = sscin_2x_size * UPPER_HODO_X_PADDLES / 2.
315           ! half width of hodoscope in y
316 cdaq  1.1       par(2) = sscin_2y_size * UPPER_HODO_Y_PADDLES / 2.
317           ! half thickness of hodoscope in z, times 2 because of stagger
318                 par(3) = HODO_THICKNESS * hodoscale
319                 call g_ugsvolu ('HDX2', 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
320                 call g_ugsvolu ('HDY2', 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
321           
322           ! box for front hodos
323           ! half width of hodoscope in x
324                 par(1) = sscin_1x_size * LOWER_HODO_X_PADDLES / 2.
325           ! half width of hodoscope in y
326                 par(2) = sscin_1y_size * LOWER_HODO_Y_PADDLES / 2.
327                 par(3) = HODO_THICKNESS*hodoscale + (sscin_1y_zpos-sscin_1x_zpos)/2.
328                 call g_ugsvolu ('HOD1', 'BOX ', DETMEDIA, par, 3, ivolu) ! hodoscope box
329                 call gsatt ('HOD1', 'SEEN', 0)	! can't see the hodo box
330           
331           ! box for back hodos
332           ! half width of hodoscope in x
333                 par(1) = sscin_2x_size * UPPER_HODO_X_PADDLES / 2.
334           ! half width of hodoscope in y
335                 par(2) = sscin_2y_size * UPPER_HODO_Y_PADDLES / 2.
336                 par(3) = HODO_THICKNESS*hodoscale + (sscin_2y_zpos-sscin_2x_zpos)/2.
337 cdaq  1.1       call g_ugsvolu ('HOD2', 'BOX ', DETMEDIA, par, 3, ivolu) ! hodoscope box
338                 call gsatt ('HOD2', 'SEEN', 0)	! can't see the hodo box
339           *                                         added by Derek
340           *
341                 x = HODO_LOWER_X_OFFSET
342                 y = HODO_LOWER_Y_OFFSET
343                 z = sscin_1x_zpos
344                 call gspos ('HOD1', 1, 'SHUT', x, y, z, 0, 'ONLY') ! lower hodo
345                 x = HODO_UPPER_X_OFFSET
346                 y = HODO_UPPER_Y_OFFSET
347                 z = sscin_2x_zpos
348                 call gspos ('HOD2', 1, 'SHUT', x, y, z, 0, 'ONLY') ! upper hodo
349           
350                 z= -(HODO_THICKNESS*hodoscale + (sscin_1y_zpos-sscin_1x_zpos))/2.
351                 call gspos ('HDX1', 1, 'HOD1', 0., 0., z, 0, 'ONLY') ! X plane
352                 call gspos ('HDY1', 1, 'HOD1', 0., 0., -z, 0, 'ONLY') ! Y plane
353                 z= -(HODO_THICKNESS*hodoscale + (sscin_2y_zpos-sscin_2x_zpos))/2.
354                 call gspos ('HDX2', 1, 'HOD2', 0., 0., z, 0, 'ONLY') ! X plane
355                 call gspos ('HDY2', 1, 'HOD2', 0., 0., -z, 0, 'ONLY') ! Y plane
356           
357           * Now define the strips for the hodoscopes
358 cdaq  1.1 
359                 x = (LOWER_HODO_X_PADDLES + 1.) * sscin_1x_size / 2. ! starting loci
360                 do i = 1, LOWER_HODO_X_PADDLES
361                   x = x - sscin_1x_size
362                   write (scinname,'(a,a)') 'H1X',char(64 + i)
363           *        call gspos ('HOX1', i, 'HDX1', x, 0., 0., 0, 'ONLY')
364                   par(1) = sscin_1x_size / 2. ! half width of X strips
365                   par(2) = sscin_1y_size * LOWER_HODO_Y_PADDLES / 2.
366                                                  ! half width of hodoscope in y
367                   par(3) = HODO_THICKNESS * hodoscale / 2. !half thickness of hodoscope in z
368                   call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
369                   call gspos (scinname, i, 'HDX1', x, 0., 0., 0, 'ONLY')
370                 enddo
371                 y = (LOWER_HODO_Y_PADDLES + 1.) * sscin_1y_size / 2. ! starting loci
372                 do i = 1, LOWER_HODO_Y_PADDLES
373                   y = y - sscin_1y_size
374                   write (scinname,'(a,a)') 'H1Y',char(64 + i)
375                   par(1) = sscin_1x_size * LOWER_HODO_X_PADDLES / 2.
376                                                   ! half width of hodoscope in x
377                   par(2) = sscin_1y_size / 2.	! half width of X strips
378                   par(3) = HODO_THICKNESS * hodoscale / 2. !half thickness of hodoscope in z
379 cdaq  1.1         call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! Y plane hodo
380                   call gspos (scinname, i, 'HDY1', 0., y, 0., 0, 'ONLY')
381                 enddo
382                 x = (UPPER_HODO_X_PADDLES + 1.) * sscin_2x_size / 2. ! starting loci
383                 do i = 1,UPPER_HODO_X_PADDLES
384                   x = x - sscin_2x_size
385                   write (scinname,'(a,a)') 'H2X',char(64 + i)
386                   par(1) = sscin_2x_size / 2. ! half width of X strips
387                   par(2) = sscin_2y_size * UPPER_HODO_Y_PADDLES / 2.
388                                                     ! half width of hodoscope in y
389                   par(3) = HODO_THICKNESS * hodoscale / 2. !half thickness of hodoscope in z
390                   call g_ugsvolu (scinname, 'BOX ', DETMEDIA, par, 3, ivolu) ! X plane hodo
391                   call gspos (scinname, i, 'HDX2', x, 0., 0., 0, 'ONLY')
392                 enddo
393                 y = (UPPER_HODO_Y_PADDLES + 1.) * sscin_2y_size / 2. ! starting loci
394                 do i = 1, UPPER_HODO_Y_PADDLES
395                   y = y - sscin_2y_size
396                   write (scinname,'(a,a)') 'H2Y',char(64 + i)
397                   par(1) = sscin_2x_size * UPPER_HODO_X_PADDLES / 2.
398                                                   ! half width of hodoscope in x
399                   par(2) = sscin_2y_size / 2.	! half width of X strips
400 cdaq  1.1         par(3) = HODO_THICKNESS * hodoscale / 2. !half thickness of hodoscope in z
401                   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 cdaq  1.1 
422           ! 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 cdaq  1.1 
443                 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                 do ilayer =1,SMAX_CAL_COLUMNS
447                    do irow = 1,SMAX_CAL_ROWS
448                       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                 do ilayer =1,SMAX_CAL_COLUMNS
454                    x =  (smax_cal_rows - 1.) / 2. * scal_block_zsize
455                    do irow = 1,SMAX_CAL_ROWS
456                       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 cdaq  1.1 *
464           
465                 end

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